From git at git.haskell.org Thu Dec 1 00:11:21 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Dec 2016 00:11:21 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add another testcase for #11821 (6c54fa5) Message-ID: <20161201001121.C9EE23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6c54fa512c4280e8047ba7891d42ba14bb88b149/ghc >--------------------------------------------------------------- commit 6c54fa512c4280e8047ba7891d42ba14bb88b149 Author: Ben Gamari Date: Wed Nov 30 19:09:11 2016 -0500 testsuite: Add another testcase for #11821 >--------------------------------------------------------------- 6c54fa512c4280e8047ba7891d42ba14bb88b149 testsuite/tests/polykinds/T11821a.hs | 4 ++++ testsuite/tests/polykinds/all.T | 1 + 2 files changed, 5 insertions(+) diff --git a/testsuite/tests/polykinds/T11821a.hs b/testsuite/tests/polykinds/T11821a.hs new file mode 100644 index 0000000..da96fe2 --- /dev/null +++ b/testsuite/tests/polykinds/T11821a.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE GADTs, TypeInType, ConstraintKinds #-} +module T11821a where +import Data.Proxy +type SameKind (a :: k1) (b :: k2) = ('Proxy :: Proxy k1) ~ ('Proxy :: Proxy k2) diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index db06932..c5ec8ac 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -147,6 +147,7 @@ test('T11648', normal, compile, ['']) test('T11648b', normal, compile_fail, ['']) test('KindVType', normal, compile_fail, ['']) test('T11821', normal, compile, ['']) +test('T11821a', normal, compile, ['']) test('T11640', normal, compile, ['']) test('T11554', normal, compile_fail, ['']) test('T12055', normal, compile, ['']) From git at git.haskell.org Thu Dec 1 02:42:05 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Dec 2016 02:42:05 +0000 (UTC) Subject: [commit: ghc] master: Fix typo in functional dependencies doc (0200ded) Message-ID: <20161201024205.2355C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0200dedc32122a939fc9e7ed83b01e527d7b3808/ghc >--------------------------------------------------------------- commit 0200dedc32122a939fc9e7ed83b01e527d7b3808 Author: Chris Martin Date: Wed Nov 30 21:41:49 2016 -0500 Fix typo in functional dependencies doc Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2772 >--------------------------------------------------------------- 0200dedc32122a939fc9e7ed83b01e527d7b3808 docs/users_guide/glasgow_exts.rst | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 12c2def..912f9ae 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -4937,7 +4937,8 @@ Functional dependencies Allow use of functional dependencies in class declarations. -Functional dependencies are implemented as described by [Jones2000]_.Mark Jones in +Functional dependencies are implemented as described by Mark Jones in +[Jones2000]_. Functional dependencies are introduced by a vertical bar in the syntax of a class declaration; e.g. :: From git at git.haskell.org Thu Dec 1 17:24:00 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Dec 2016 17:24:00 +0000 (UTC) Subject: [commit: ghc] master: Ensure flags destined for ld are properly passed (f48f5a9e) Message-ID: <20161201172400.C6AC93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f48f5a9ebf384e1e157b7b413e1d779f4289ddd2/ghc >--------------------------------------------------------------- commit f48f5a9ebf384e1e157b7b413e1d779f4289ddd2 Author: Ben Gamari Date: Thu Dec 1 11:28:47 2016 -0500 Ensure flags destined for ld are properly passed GHC uses gcc, not ld, for linking. Consequently all flags to be interpreted by ld need to be prefixed by -optl,-Wl on the GHC command line. Test Plan: Validate on OpenBSD Reviewers: austin, rwbarton Reviewed By: rwbarton Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2776 >--------------------------------------------------------------- f48f5a9ebf384e1e157b7b413e1d779f4289ddd2 rules/distdir-way-opts.mk | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rules/distdir-way-opts.mk b/rules/distdir-way-opts.mk index 6ae9807..602e6eb 100644 --- a/rules/distdir-way-opts.mk +++ b/rules/distdir-way-opts.mk @@ -207,7 +207,7 @@ $1_$2_$3_ALL_LD_OPTS = \ # Options for passing to GHC when we use it for linking $1_$2_$3_GHC_LD_OPTS = \ - $$(addprefix -optl, $$($1_$2_$3_ALL_LD_OPTS)) \ + $$(addprefix -optl-Wl, $$($1_$2_$3_ALL_LD_OPTS)) \ $$($1_$2_$3_MOST_HC_OPTS) $1_$2_$3_ALL_AS_OPTS = \ From git at git.haskell.org Thu Dec 1 17:53:06 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Dec 2016 17:53:06 +0000 (UTC) Subject: [commit: ghc] master: Levity polymorphic expressions mustn't be floated-out in let-bindings. (514c01e) Message-ID: <20161201175306.47BED3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/514c01eec5f2b23f278c29b61345dce6c37900f1/ghc >--------------------------------------------------------------- commit 514c01eec5f2b23f278c29b61345dce6c37900f1 Author: Sylvain Henry Date: Thu Dec 1 12:24:34 2016 -0500 Levity polymorphic expressions mustn't be floated-out in let-bindings. Reviewers: simonpj, austin, bgamari Reviewed By: simonpj, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2769 GHC Trac Issues: #12901 >--------------------------------------------------------------- 514c01eec5f2b23f278c29b61345dce6c37900f1 compiler/simplCore/SetLevels.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/compiler/simplCore/SetLevels.hs b/compiler/simplCore/SetLevels.hs index f2f373d..dc36a6c 100644 --- a/compiler/simplCore/SetLevels.hs +++ b/compiler/simplCore/SetLevels.hs @@ -83,6 +83,7 @@ import Demand ( StrictSig ) import Name ( getOccName, mkSystemVarName ) import OccName ( occNameString ) import Type ( isUnliftedType, Type, mkLamTypes ) +import Kind ( isLevityPolymorphic, typeKind ) import BasicTypes ( Arity, RecFlag(..) ) import UniqSupply import Util @@ -487,6 +488,9 @@ lvlMFE strict_ctxt env ann_expr -- Can't let-bind it; see Note [Unlifted MFEs] -- This includes coercions, which we don't want to float anyway -- NB: no need to substitute cos isUnliftedType doesn't change + || isLevityPolymorphic (typeKind (exprType expr)) + -- We can't let-bind levity polymorphic expressions + -- See Note [Levity polymorphism invariants] in CoreSyn || notWorthFloating ann_expr abs_vars || not float_me = -- Don't float it out From git at git.haskell.org Thu Dec 1 17:53:08 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Dec 2016 17:53:08 +0000 (UTC) Subject: [commit: ghc] master: Make note of #12907 in 8.0.2 release notes (a452c6e) Message-ID: <20161201175308.EFC283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a452c6e57a286f3b31f0e3fbef83cbea0cee8b34/ghc >--------------------------------------------------------------- commit a452c6e57a286f3b31f0e3fbef83cbea0cee8b34 Author: Ryan Scott Date: Thu Dec 1 12:24:48 2016 -0500 Make note of #12907 in 8.0.2 release notes Test Plan: Read it, commit it, merge it, ship it Reviewers: goldfire, bgamari, austin, hvr, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2774 GHC Trac Issues: #12907 >--------------------------------------------------------------- a452c6e57a286f3b31f0e3fbef83cbea0cee8b34 docs/users_guide/8.0.2-notes.rst | 13 +++++++++++++ 1 file changed, 13 insertions(+) diff --git a/docs/users_guide/8.0.2-notes.rst b/docs/users_guide/8.0.2-notes.rst index 9bc78ea..fa7aa8d 100644 --- a/docs/users_guide/8.0.2-notes.rst +++ b/docs/users_guide/8.0.2-notes.rst @@ -86,6 +86,19 @@ Language instance {-# OVERLAPPING #-} Foo Int +- GHC now adheres more closely to the Haskell 2010 Report with respect to + defaulting rules. As a result, GHC will now reject some defaulting rules + which GHC 8.0.1 and earlier would accept. For example, this is now + rejected :: + + module Foo where + default (Bool) + + because when the :ghc-flag:`-XExtendedDefaultRules` extension is not + enabled, defaulting rules only work for the ``Num`` class, of which ``Bool`` + is not an instance. To make GHC accept the above program, simply enable the + :ghc-flag:`-XExtendedDefaultRules` extension. + Compiler ~~~~~~~~ From git at git.haskell.org Thu Dec 1 17:53:11 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Dec 2016 17:53:11 +0000 (UTC) Subject: [commit: ghc] master: rts: Fix type of bool literal (0ac5e0c) Message-ID: <20161201175311.AAFA23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0ac5e0cb9afc9c15386f381ed41bf514ee2ffde7/ghc >--------------------------------------------------------------- commit 0ac5e0cb9afc9c15386f381ed41bf514ee2ffde7 Author: Ben Gamari Date: Thu Dec 1 12:25:00 2016 -0500 rts: Fix type of bool literal Test Plan: Build `p` way Reviewers: austin, erikd, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2779 >--------------------------------------------------------------- 0ac5e0cb9afc9c15386f381ed41bf514ee2ffde7 rts/Exception.cmm | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/Exception.cmm b/rts/Exception.cmm index 2a07eaa..a27227d 100644 --- a/rts/Exception.cmm +++ b/rts/Exception.cmm @@ -456,7 +456,7 @@ stg_raisezh /* explicit stack */ /* ToDo: currently this is a hack. Would be much better if * the info was only displayed for an *uncaught* exception. */ - if (RtsFlags_ProfFlags_showCCSOnException(RtsFlags) != 0::I32) { + if (RtsFlags_ProfFlags_showCCSOnException(RtsFlags) != 0::CBool) { SAVE_THREAD_STATE(); ccall fprintCCS_stderr(CCCS "ptr", exception "ptr", From git at git.haskell.org Thu Dec 1 18:27:42 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Dec 2016 18:27:42 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Remove Unicode literals from driver (7214e92) Message-ID: <20161201182742.42D4C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7214e924ca690946288ccf681ef652cee3cb114c/ghc >--------------------------------------------------------------- commit 7214e924ca690946288ccf681ef652cee3cb114c Author: Ben Gamari Date: Thu Dec 1 12:53:31 2016 -0500 testsuite: Remove Unicode literals from driver They are not supported by Python 3.0, 3.1, and 3.2 (but are supported by >= 3.3; silliness!) Test Plan: Validate on python 3.2 Reviewers: austin Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D2778 GHC Trac Issues: #12909, #9184 >--------------------------------------------------------------- 7214e924ca690946288ccf681ef652cee3cb114c testsuite/driver/testlib.py | 24 ++++++++++++------------ 1 file changed, 12 insertions(+), 12 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index b0252de..7e7d994 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1283,17 +1283,17 @@ def interpreter_run(name, way, extra_hc_opts, top_mod): with io.open(script, 'w', encoding='utf8') as f: # set the prog name and command-line args to match the compiled # environment. - f.write(u':set prog ' + name + u'\n') - f.write(u':set args ' + opts.extra_run_opts + u'\n') + f.write(':set prog ' + name + '\n') + f.write(':set args ' + opts.extra_run_opts + '\n') # Add marker lines to the stdout and stderr output files, so we # can separate GHCi's output from the program's. - f.write(u':! echo ' + delimiter) - f.write(u':! echo 1>&2 ' + delimiter) + f.write(':! echo ' + delimiter) + f.write(':! echo 1>&2 ' + delimiter) # Set stdout to be line-buffered to match the compiled environment. - f.write(u'System.IO.hSetBuffering System.IO.stdout System.IO.LineBuffering\n') + f.write('System.IO.hSetBuffering System.IO.stdout System.IO.LineBuffering\n') # wrapping in GHC.TopHandler.runIO ensures we get the same output # in the event of an exception as for the compiled program. - f.write(u'GHC.TopHandler.runIOFastExit Main.main Prelude.>> Prelude.return ()\n') + f.write('GHC.TopHandler.runIOFastExit Main.main Prelude.>> Prelude.return ()\n') stdin = in_testdir(opts.stdin if opts.stdin else add_suffix(name, 'stdin')) if os.path.exists(stdin): @@ -1568,7 +1568,7 @@ def compare_outputs(way, kind, normaliser, expected_file, actual_file, def normalise_whitespace( str ): # Merge contiguous whitespace characters into a single space. - return u' '.join(w for w in str.split()) + return ' '.join(w for w in str.split()) callSite_re = re.compile(r', called at (.+):[\d]+:[\d]+ in [\w\-\.]+:') @@ -1621,7 +1621,7 @@ def normalise_errmsg( str ): # Also filter out bullet characters. This is because bullets are used to # separate error sections, and tests shouldn't be sensitive to how the # the division happens. - bullet = u'•'.encode('utf8') if isinstance(str, bytes) else u'•' + bullet = '•'.encode('utf8') if isinstance(str, bytes) else '•' str = str.replace(bullet, '') return str @@ -1712,7 +1712,7 @@ def normalise_asm( str ): out.append(instr[0] + ' ' + instr[1]) else: out.append(instr[0]) - out = u'\n'.join(out) + out = '\n'.join(out) return out def if_verbose( n, s ): @@ -1747,8 +1747,8 @@ def runCmd(cmd, stdin=None, stdout=None, stderr=None, timeout_multiplier=1.0): with io.open(stdin, 'rb') as f: stdin_buffer = f.read() - stdout_buffer = u'' - stderr_buffer = u'' + stdout_buffer = '' + stderr_buffer = '' hStdErr = subprocess.PIPE if stderr is subprocess.STDOUT: @@ -1978,7 +1978,7 @@ def printTestInfosSummary(file, testInfos): file.write('\n') def modify_lines(s, f): - s = u'\n'.join([f(l) for l in s.splitlines()]) + s = '\n'.join([f(l) for l in s.splitlines()]) if s and s[-1] != '\n': # Prevent '\ No newline at end of file' warnings when diffing. s += '\n' From git at git.haskell.org Thu Dec 1 18:27:45 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Dec 2016 18:27:45 +0000 (UTC) Subject: [commit: ghc] master: rts: Ensure we always give MADV_DONTNEED a chance in osDecommitMemory (6576bf8) Message-ID: <20161201182745.067CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6576bf83cdf4eac05eb88a24aa934a736c91e3da/ghc >--------------------------------------------------------------- commit 6576bf83cdf4eac05eb88a24aa934a736c91e3da Author: Ben Gamari Date: Thu Dec 1 12:55:23 2016 -0500 rts: Ensure we always give MADV_DONTNEED a chance in osDecommitMemory As described in #12865, newer Linux kernels support both MADV_FREE and MADV_DONTNEED. Previously a runtime would fail to try MADV_DONTNEED if MADV_FREE failed (e.g. since the kernel which the image is running on doesn't support the latter). Now we try MADV_DONTNEED if MADV_FREE failed to ensure that binaries compiled on a kernel supporting MADV_FREE don't fail on decommit. Test Plan: Validate Reviewers: austin, erikd, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2780 GHC Trac Issues: #12865 >--------------------------------------------------------------- 6576bf83cdf4eac05eb88a24aa934a736c91e3da rts/posix/OSMem.c | 19 ++++++++++++++++--- 1 file changed, 16 insertions(+), 3 deletions(-) diff --git a/rts/posix/OSMem.c b/rts/posix/OSMem.c index 5291745..beffeda 100644 --- a/rts/posix/OSMem.c +++ b/rts/posix/OSMem.c @@ -541,11 +541,24 @@ void osDecommitMemory(void *at, W_ size) #ifdef MADV_FREE // Try MADV_FREE first, FreeBSD has both and MADV_DONTNEED - // just swaps memory out + // just swaps memory out. Linux >= 4.5 has both DONTNEED and FREE; either + // will work as they both allow the system to free anonymous pages. + // It is important that we try both methods as the kernel which we were + // built on may differ from the kernel we are now running on. r = madvise(at, size, MADV_FREE); -#else - r = madvise(at, size, MADV_DONTNEED); + if(r < 0) { + if (errno == EINVAL) { + // Perhaps the system doesn't support MADV_FREE; fall-through and + // try MADV_DONTNEED. + } else { + sysErrorBelch("unable to decommit memory"); + } + } else { + return; + } #endif + + r = madvise(at, size, MADV_DONTNEED); if(r < 0) sysErrorBelch("unable to decommit memory"); } From git at git.haskell.org Thu Dec 1 18:38:44 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Dec 2016 18:38:44 +0000 (UTC) Subject: [commit: ghc] master: Typos in comments (0f37550) Message-ID: <20161201183844.430AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0f37550c797b08b953049fb84f6ea127e4d7668c/ghc >--------------------------------------------------------------- commit 0f37550c797b08b953049fb84f6ea127e4d7668c Author: Gabor Greif Date: Thu Dec 1 18:46:35 2016 +0100 Typos in comments >--------------------------------------------------------------- 0f37550c797b08b953049fb84f6ea127e4d7668c compiler/coreSyn/MkCore.hs | 2 +- compiler/main/DynFlags.hs | 4 ++-- compiler/main/HeaderInfo.hs | 2 +- compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcFlatten.hs | 2 +- compiler/typecheck/TcSMonad.hs | 2 +- libraries/base/Control/Exception.hs | 2 +- libraries/base/tests/unicode001.hs | 2 +- libraries/integer-gmp/src/GHC/Integer/Type.hs | 2 +- testsuite/tests/simplCore/should_run/simplrun007.hs | 2 +- testsuite/tests/typecheck/should_compile/T12427a.hs | 2 +- testsuite/tests/typecheck/should_compile/T2357.hs | 2 +- 12 files changed, 13 insertions(+), 13 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0f37550c797b08b953049fb84f6ea127e4d7668c From git at git.haskell.org Thu Dec 1 20:05:43 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Dec 2016 20:05:43 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Actually update haddock.compiler allocations (a934e25) Message-ID: <20161201200543.320F23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a934e2569c6cd5f24ff3302d48a44a4bdd674c97/ghc >--------------------------------------------------------------- commit a934e2569c6cd5f24ff3302d48a44a4bdd674c97 Author: Ben Gamari Date: Thu Dec 1 15:04:44 2016 -0500 testsuite: Actually update haddock.compiler allocations The previous attempt updated the comment but not the value. Silly me. >--------------------------------------------------------------- a934e2569c6cd5f24ff3302d48a44a4bdd674c97 testsuite/tests/perf/haddock/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index 712debb..dee39fc 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -112,7 +112,7 @@ test('haddock.Cabal', test('haddock.compiler', [unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 55314944264, 10) + [(wordsize(64), 60911147344, 10) # 2012P-08-14: 26070600504 (amd64/Linux) # 2012-08-29: 26353100288 (amd64/Linux, new CG) # 2012-09-18: 26882813032 (amd64/Linux) From git at git.haskell.org Thu Dec 1 22:31:20 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Dec 2016 22:31:20 +0000 (UTC) Subject: [commit: ghc] wip/T12819: Reshuffle levity polymorphism checks. (37bb95b) Message-ID: <20161201223120.613773A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12819 Link : http://ghc.haskell.org/trac/ghc/changeset/37bb95bb57024c60b4eb7eef040efcedadf89894/ghc >--------------------------------------------------------------- commit 37bb95bb57024c60b4eb7eef040efcedadf89894 Author: Richard Eisenberg Date: Thu Nov 10 13:41:30 2016 -0500 Reshuffle levity polymorphism checks. Previously, GHC checked for bad levity polymorphism to the left of all arrows in data constructors. This was wrong, as reported in #12911 (where an example is also shown). The solution is to check each individual argument for bad levity polymorphism. Thus the check has been moved from TcValidity to TcTyClsDecls. A similar situation exists with pattern synonyms, also fixed here. This patch also nabs #12819 while I was in town. Test cases: typecheck/should_compile/T12911, patsyn/should_fail/T12819 >--------------------------------------------------------------- 37bb95bb57024c60b4eb7eef040efcedadf89894 compiler/typecheck/TcSigs.hs | 28 +++++++++++++++++----- compiler/typecheck/TcTyClsDecls.hs | 2 ++ compiler/typecheck/TcValidity.hs | 14 +---------- compiler/types/Type.hs | 5 ++-- testsuite/tests/patsyn/should_fail/T12819.hs | 9 +++++++ testsuite/tests/patsyn/should_fail/all.T | 1 + testsuite/tests/typecheck/should_compile/T12911.hs | 9 +++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 8 files changed, 48 insertions(+), 21 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 37bb95bb57024c60b4eb7eef040efcedadf89894 From git at git.haskell.org Thu Dec 1 22:31:23 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Dec 2016 22:31:23 +0000 (UTC) Subject: [commit: ghc] wip/T12819's head updated: Reshuffle levity polymorphism checks. (37bb95b) Message-ID: <20161201223123.9B30E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T12819' now includes: 500d90d ghc-cabal: Use correct name of linker flags env variable 816d2e4 build system: Include CONF_LD_LINKER_OPTS in ALL_LD_OPTS 9030d8e configure: Pass HC_OPTS_STAGEx to build system bae4a55 Pass -no-pie to GCC 0a122a4 testsuite: Update allocation numbers for T5631 e06e21a Add Richard Eisenberg's new email to mailmap bef7e78 Read parentheses better 122d826 rts: Add api to pin a thread to a numa node but without fixing a capability aa10c67 rts/linker: Move loadArchive to new source file e8ae4dc Update user's guide after D2490 03e8d26 Prevent GND from inferring an instance context for method-less classes 60bb9d1 Revert "Pass -no-pie to GCC" 7a7bb5d Revert "Refactor CallStack defaulting slightly" ec0bf81 rts: Fix LoadArchive on OS X d421a7e Pass -no-pie to GCC 46e2bef testsuite: Lower allocations for T876 7eae862 ghc-pkg: Munge dynamic library directories 2cfbee8 rts: Fix build when linked with gold 4e0b8f4 rts: Fix #include of 587dccc Make default output less verbose (source/object paths) 568e003 template-haskell: Version bump ca1b986 ghc: Fix ghc's template-haskell bound 8cb7bc5 rts: Fix references to UChar 6c0f10f Kill Type pretty-printer 55d535d Remove CONSTR_STATIC 034e01e Accept output for scc003 e0ca7ff Fix numa001 failure with "too many NUMA nodes" cb16890 testsuite: Fix creep of T4029 011af2b configure: Verify that GCC recognizes -no-pie flag 1b336d9 Skip 64-bit symbol tables 98f9759 Hopefully fix build on OS X 642adec Mark T12041 as expect_broken with -DDEBUG (#12826) 017d11e Typos in comments, notes and manual 31d5b6e fixup! Stop the simplifier from removing StaticPtr binds. 0e58652 Test for unnecessary register spills 4a835f0 Update xhtml submodule a637eeb Don't use mmap symbols when !RTS_LINKER_USE_MMAP 0135188 Storage.c: Pass a size to sys_icache_invalidate fa70b1e Fix -fobject-code with -fexternal-interpreter 7acee06 Avoid calling newDynFlags when there are no changes d3542fa Generalise the implicit prelude import 8dfca69 Inline compiler/NOTES into X86/Ppr.hs b769586 Fix windows validate 31398fb Test for type synonym loops on TyCon. 2878604 Correct spelling of command-line option in comment cede770 Correct name of Note in comment 07e40e9 Add Data instance for Const 18eb57b Revert "Add Data instance for Const" 9a4983d Pass autoconf triplets to sub-project configures 20fb781 LLVM generate llvm.expect for conditional branches 4d4f353 testsuite: Rip out hack for #12554 04b024a GHCi: Unconditionally import System.Directory 231a3ae Have reify work for local variables with functional dependencies. 9c39e09 Switch to LLVM version 3.9 94d1221 Add missing SMP symbols to RT linker. d328abc Spelling in comment only 3bd1dd4 Add Data instance for Const 4b72f85 Optimise whole module exports 6ad94d8 Updated code comment regarding EquationInfo. Trac #12856 ea37b83 A few typos in comments 5bce207 testsuite: Add test for #12855 926469f testsuite: Add test for #12024 b98dbdf testsuite: Add (still broken) testcase for #12447 e7ec521 testsuite: Add (still failing) testcase for #12550 ea76a21 add ieee754 next* functions to math_funs 514acfe Implement fine-grained `-Werror=...` facility 4c0dc76 Ignore Hadrian build products. 7e4b611 Make transformers upstream repository location consistent with others 1399c8b ghc/hschooks.c: Fix include path of Rts.h f430253 Allow to unregister threadWaitReadSTM action. 14ac372 Collect wildcards in sum types during renaming (#12711) d081fcf Make quoting and reification return the same types 9a431e5 Make a panic into an ASSERT 0476a64 Fix a bug in mk_superclasses_of f04f118 Comments only in TcType 0123efd Add elemDVarEnv 1eec1f2 Another major constraint-solver refactoring 18d0bdd Allow TyVars in TcTypes 4431e48 Remove redundant kind check 90a65ad Perf improvements in T6048, T10547 e319466 Typos in comments c1b4b76 Fix a name-space problem with promotion f0f4682 Test Trac #12867 83a952d Test Trac #12845 a5a3926 Kill off ifaceTyVarsOfType bc35c3f Use 'v' instead of 'tpl' for template vars edbe831 Use TyVars in a DFunUnfolding 12eff23 Use TyVars in PatSyns 5f349fe Improve pretty-printing of types eb55ec2 Refactor functional dependencies a bit 1bfff60 Fix inference of partial signatures 086b483 A tiny bit more tc tracing f8c966c Be a bit more selective about improvement 6ec2304 Fix an long-standing bug in OccurAnal 5238842 Typos in comments only [ci skip] 605af54 Test Trac #12776 27a6bdf Test Trac #12885 3aa9368 Comments only (related to #12789) abd4a4c Make note of #12881 in 8.0.2 release notes f8c8de8 Zonk the free tvs of a RULE lhs to TyVars e755930 Typos in comments 36e3622 Store string as parsed in SourceText for CImport 1732d7a Define thread primitives if they're supported. 30cecae users_guide: Bring 8.0.2 release notes up-to-date with ghc-8.0 branch f1fc8cb Make diagnostics slightly more colorful 52222f9b Detect color support da5a61e Minor cleanup of foldRegs{Used,Defd} 2d99da0 testsuite: Mention CLEANUP option in README 3ec8563 Replace -fshow-source-paths with -fhide-source-paths c2268ba Refactor Pattern Match Checker to use ListT 6845087 Purge GHC of literate Perl 4d4e7a5 Use newBlockId instead of newLabelC 7753273 AsmCodeGen: Refactor worker in cmmNativeGens 6d5c2e7 NCGMonad: Add MonadUnique NatM instance eaed140 OrdList: Add Foldable, Traversable instances fe3748b testsuite: Bump haddock.compiler allocations 795f8bd hschooks.c: Ensure correct header file is included 6f7ed1e Make globals use sharedCAF 56d7451 Fix type of GarbageCollect declaration 428e152 Use C99's bool 758b81d rts: Add missing #include 23dc6c4 Remove most functions from cmm/BlockId b92f8e3 Added Eq1, Ord1, Read1 and Show1 instances for NonEmpty 679ccd1 Hoopl/Dataflow: use block-oriented interface 0ce59be Fix testsuite threading, timeout, encoding and performance issues on Windows dd9ba50 Update test output for Windows 605bb9b testsuite: Use python3 by default 20c0614 Update Mingw-w64 bindist for Windows ef37580 Fix windows validate. be8a47f Tweaks to grammar and such. 03766cd Rename RuntimeRepPolymorphism to LevityPolymorphism e2330b6 Revert "Make globals use sharedCAF" c2a2911 Revert "Fix windows validate." 6c54fa5 testsuite: Add another testcase for #11821 0200ded Fix typo in functional dependencies doc f48f5a9e Ensure flags destined for ld are properly passed 514c01e Levity polymorphic expressions mustn't be floated-out in let-bindings. a452c6e Make note of #12907 in 8.0.2 release notes 0ac5e0c rts: Fix type of bool literal 7214e92 testsuite: Remove Unicode literals from driver 6576bf8 rts: Ensure we always give MADV_DONTNEED a chance in osDecommitMemory 0f37550 Typos in comments a934e25 testsuite: Actually update haddock.compiler allocations 37bb95b Reshuffle levity polymorphism checks. From git at git.haskell.org Thu Dec 1 23:34:20 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Dec 2016 23:34:20 +0000 (UTC) Subject: [commit: ghc] master: testsuite/conc059: Don't attempt to use stdcall where it isn't supported (7fafb84) Message-ID: <20161201233420.04D443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7fafb84e9fd61417094f41b4a5d88bbef6df7aa5/ghc >--------------------------------------------------------------- commit 7fafb84e9fd61417094f41b4a5d88bbef6df7aa5 Author: Ben Gamari Date: Thu Dec 1 16:58:34 2016 -0500 testsuite/conc059: Don't attempt to use stdcall where it isn't supported Test Plan: Validate on 64-bit Windows Reviewers: geekosaur, austin, erikd, Phyx Reviewed By: Phyx Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2781 >--------------------------------------------------------------- 7fafb84e9fd61417094f41b4a5d88bbef6df7aa5 testsuite/tests/concurrent/should_run/conc059.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/concurrent/should_run/conc059.hs b/testsuite/tests/concurrent/should_run/conc059.hs index bed28d2..148c0ba 100644 --- a/testsuite/tests/concurrent/should_run/conc059.hs +++ b/testsuite/tests/concurrent/should_run/conc059.hs @@ -19,7 +19,15 @@ f x = do foreign export ccall "f" f :: Int -> IO () #ifdef mingw32_HOST_OS -foreign import stdcall safe "Sleep" _sleep :: Int -> IO () +# if defined(i386_HOST_ARCH) +# define WINDOWS_CCONV stdcall +# elif defined(x86_64_HOST_ARCH) +# define WINDOWS_CCONV ccall +# else +# error Unknown mingw32 arch +# endif + +foreign import WINDOWS_CCONV safe "Sleep" _sleep :: Int -> IO () usleep n = _sleep (n `quot` 1000) #else foreign import ccall safe "usleep" usleep :: Int -> IO () From git at git.haskell.org Thu Dec 1 23:34:22 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Dec 2016 23:34:22 +0000 (UTC) Subject: [commit: ghc] master: Fix naming of the native latin1 encodings (747e77c) Message-ID: <20161201233422.B13B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/747e77c9968ab09e11e78fe028bea8e1e3e97a48/ghc >--------------------------------------------------------------- commit 747e77c9968ab09e11e78fe028bea8e1e3e97a48 Author: Kai Ruemmler Date: Thu Dec 1 17:59:50 2016 -0500 Fix naming of the native latin1 encodings textEncodingName is notjust a string, it must be a valid input for mkTextEncoding, as stated in libraries/base/GHC/IO/Encoding/Types.hs. Test Plan: A working latin1 locale is required on the system. Reason: ghc's initial locale encoding defaults to ASCII, if either an unknown locale or unknown charset is used. For the bug to show up, ghc must start up using the latin1 encoding. From main directory in ghc do: $ ./configure && make clean && make boot && make inplace/bin/ghc-stage2 $ LC_CTYPE="de_DE.ISO-8859-1" ./inplace/bin/ghc-stage2 Before the patch, the last line leads to the exception thrown: ghc-stage2: mkTextEncoding: does not exist (unknown encoding:ISO8859-1(checked)//TRANSLIT) After the patch, ghc-stage2 prints a short usage summary as expected. Moreover, $ make test TEST=encoding005 continues to pass after the patch. Reviewers: austin, hvr, rwbarton, bgamari Reviewed By: bgamari Subscribers: mpickering, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D2667 >--------------------------------------------------------------- 747e77c9968ab09e11e78fe028bea8e1e3e97a48 libraries/base/GHC/IO/Encoding/Latin1.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/base/GHC/IO/Encoding/Latin1.hs b/libraries/base/GHC/IO/Encoding/Latin1.hs index efef240..730379e 100644 --- a/libraries/base/GHC/IO/Encoding/Latin1.hs +++ b/libraries/base/GHC/IO/Encoding/Latin1.hs @@ -50,7 +50,7 @@ latin1 = mkLatin1 ErrorOnCodingFailure -- | @since 4.4.0.0 mkLatin1 :: CodingFailureMode -> TextEncoding -mkLatin1 cfm = TextEncoding { textEncodingName = "ISO8859-1", +mkLatin1 cfm = TextEncoding { textEncodingName = "ISO-8859-1", mkTextDecoder = latin1_DF cfm, mkTextEncoder = latin1_EF cfm } @@ -79,7 +79,7 @@ latin1_checked = mkLatin1_checked ErrorOnCodingFailure -- | @since 4.4.0.0 mkLatin1_checked :: CodingFailureMode -> TextEncoding -mkLatin1_checked cfm = TextEncoding { textEncodingName = "ISO8859-1(checked)", +mkLatin1_checked cfm = TextEncoding { textEncodingName = "ISO-8859-1", mkTextDecoder = latin1_DF cfm, mkTextEncoder = latin1_checked_EF cfm } From git at git.haskell.org Fri Dec 2 04:01:10 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Dec 2016 04:01:10 +0000 (UTC) Subject: [commit: ghc] master: Travis: Add dependency on python3 (ddc271e) Message-ID: <20161202040110.DE6F33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ddc271e8ed6c5ec5e83dd50c6c5e77955a0e90ac/ghc >--------------------------------------------------------------- commit ddc271e8ed6c5ec5e83dd50c6c5e77955a0e90ac Author: Ben Gamari Date: Thu Dec 1 18:37:19 2016 -0500 Travis: Add dependency on python3 The testsuite now requires python >=3.0. See #12909. >--------------------------------------------------------------- ddc271e8ed6c5ec5e83dd50c6c5e77955a0e90ac .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index 0f80ece..218f5ba 100644 --- a/.travis.yml +++ b/.travis.yml @@ -21,6 +21,7 @@ addons: - ghc-7.10.3 - alex-3.1.3 - happy-1.19.4 + - python3 #- llvm-3.7 before_install: From git at git.haskell.org Fri Dec 2 16:00:50 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Dec 2016 16:00:50 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Make note of #12881 in 8.0.2 release notes (80c26da) Message-ID: <20161202160050.5AFBC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/80c26da81ff3764887f272845388248ba34cacde/ghc >--------------------------------------------------------------- commit 80c26da81ff3764887f272845388248ba34cacde Author: Ryan Scott Date: Tue Nov 29 08:43:46 2016 -0500 Make note of #12881 in 8.0.2 release notes Summary: Resolves #12881. Test Plan: Read it, commit it, merge it, ship it Reviewers: hvr, simonpj, austin, bgamari Reviewed By: simonpj Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D2760 GHC Trac Issues: #12881 (cherry picked from commit abd4a4c13e5dbaac8f1c28d8c9d9446e383f6037) >--------------------------------------------------------------- 80c26da81ff3764887f272845388248ba34cacde docs/users_guide/8.0.2-notes.rst | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/docs/users_guide/8.0.2-notes.rst b/docs/users_guide/8.0.2-notes.rst index 81f9ce4..063d947 100644 --- a/docs/users_guide/8.0.2-notes.rst +++ b/docs/users_guide/8.0.2-notes.rst @@ -71,6 +71,21 @@ Language type-checked in GHC 8.0.1 are now rejected by GHC 8.0.2. See :ghc-ticket:`12784` for details. +- Some programs which combine default type class method implementations and + overlapping instances may now fail to type-check. Here is an example: :: + + class Foo a where + foo :: a -> [a] + foo _ = [] + + instance Foo a + instance Foo Int + + The problem is that the overlapping ``Foo Int`` instance is not explicitly + marked as overlapping. To fix this, simply add an ``OVERLAPPING`` pragma: :: + + instance {-# OVERLAPPING #-} Foo Int + Compiler ~~~~~~~~ From git at git.haskell.org Fri Dec 2 16:00:53 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Dec 2016 16:00:53 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Store string as parsed in SourceText for CImport (812d9f7) Message-ID: <20161202160053.09EA93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/812d9f7f5882287f0121b8be3b446f3ee7c271ab/ghc >--------------------------------------------------------------- commit 812d9f7f5882287f0121b8be3b446f3ee7c271ab Author: Alan Zimmerman Date: Tue Nov 29 21:06:52 2016 +0200 Store string as parsed in SourceText for CImport (cherry picked from commit 36e36227e438d95fae367d10183ea43b4819854f) >--------------------------------------------------------------- 812d9f7f5882287f0121b8be3b446f3ee7c271ab compiler/parser/RdrHsSyn.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs index d79ac66..5c55127 100644 --- a/compiler/parser/RdrHsSyn.hs +++ b/compiler/parser/RdrHsSyn.hs @@ -1288,7 +1288,7 @@ mkImport cconv safety (L loc (StringLiteral esrc entity), v, ty) = -- name (cf section 8.5.1 in Haskell 2010 report). mkCImport = do let e = unpackFS entity - case parseCImport cconv safety (mkExtName (unLoc v)) e (L loc e) of + case parseCImport cconv safety (mkExtName (unLoc v)) e (L loc esrc) of Nothing -> parseErrorSDoc loc (text "Malformed entity string") Just importSpec -> returnSpec importSpec From git at git.haskell.org Fri Dec 2 16:00:55 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Dec 2016 16:00:55 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Make note of #12907 in 8.0.2 release notes (706d708) Message-ID: <20161202160055.B62303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/706d708a4bb74e27437ea2ec37e4999a4615b0e8/ghc >--------------------------------------------------------------- commit 706d708a4bb74e27437ea2ec37e4999a4615b0e8 Author: Ryan Scott Date: Thu Dec 1 12:24:48 2016 -0500 Make note of #12907 in 8.0.2 release notes Test Plan: Read it, commit it, merge it, ship it Reviewers: goldfire, bgamari, austin, hvr, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2774 GHC Trac Issues: #12907 (cherry picked from commit a452c6e57a286f3b31f0e3fbef83cbea0cee8b34) >--------------------------------------------------------------- 706d708a4bb74e27437ea2ec37e4999a4615b0e8 docs/users_guide/8.0.2-notes.rst | 13 +++++++++++++ 1 file changed, 13 insertions(+) diff --git a/docs/users_guide/8.0.2-notes.rst b/docs/users_guide/8.0.2-notes.rst index 9bc78ea..fa7aa8d 100644 --- a/docs/users_guide/8.0.2-notes.rst +++ b/docs/users_guide/8.0.2-notes.rst @@ -86,6 +86,19 @@ Language instance {-# OVERLAPPING #-} Foo Int +- GHC now adheres more closely to the Haskell 2010 Report with respect to + defaulting rules. As a result, GHC will now reject some defaulting rules + which GHC 8.0.1 and earlier would accept. For example, this is now + rejected :: + + module Foo where + default (Bool) + + because when the :ghc-flag:`-XExtendedDefaultRules` extension is not + enabled, defaulting rules only work for the ``Num`` class, of which ``Bool`` + is not an instance. To make GHC accept the above program, simply enable the + :ghc-flag:`-XExtendedDefaultRules` extension. + Compiler ~~~~~~~~ From git at git.haskell.org Fri Dec 2 16:00:59 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Dec 2016 16:00:59 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Fix inference of partial signatures (4212674) Message-ID: <20161202160059.0B6DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/4212674ba92971734eec064809f8e1a45bca992a/ghc >--------------------------------------------------------------- commit 4212674ba92971734eec064809f8e1a45bca992a Author: Simon Peyton Jones Date: Fri Nov 25 11:35:50 2016 +0000 Fix inference of partial signatures When we had f :: ( _ ) => blah we were failing to call growThetaTyVars, as we do in the no-type-signature case, and that meant that we weren't generalising over the right type variables. I'm quite surprised this didn't cause problems earlier. Anyway Trac #12844 showed it up and this patch fixes it (cherry picked from commit 1bfff60fc57cd564382b86bdfb1f2764ca15d44f) >--------------------------------------------------------------- 4212674ba92971734eec064809f8e1a45bca992a compiler/typecheck/TcBinds.hs | 7 +++++-- .../tests/partial-sigs/should_compile/T12844.hs | 20 ++++++++++++++++++++ .../tests/partial-sigs/should_compile/T12844.stderr | 6 ++++++ testsuite/tests/partial-sigs/should_compile/all.T | 1 + 4 files changed, 32 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index a1ad6be..dddae3e 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -778,8 +778,11 @@ chooseInferredQuantifiers inferred_theta tau_tvs qtvs | PartialSig { sig_cts = extra } <- bndr_info , Just loc <- extra = do { annotated_theta <- zonkTcTypes annotated_theta - ; let free_tvs = closeOverKinds (tyCoVarsOfTypes annotated_theta - `unionVarSet` tau_tvs) + ; let free_tvs = closeOverKinds (growThetaTyVars inferred_theta seed_tvs) + -- growThetaVars just like the no-type-sig case + -- Omitting this caused #12844 + seed_tvs = tyCoVarsOfTypes annotated_theta -- These are put there + `unionVarSet` tau_tvs -- by the user my_theta = pickQuantifiablePreds free_tvs annotated_theta inferred_theta -- Report the inferred constraints for an extra-constraints wildcard/hole as diff --git a/testsuite/tests/partial-sigs/should_compile/T12844.hs b/testsuite/tests/partial-sigs/should_compile/T12844.hs new file mode 100644 index 0000000..d47b82c --- /dev/null +++ b/testsuite/tests/partial-sigs/should_compile/T12844.hs @@ -0,0 +1,20 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE PartialTypeSignatures #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeOperators #-} + +module T12844 where + +barWraper :: ('(r,r') ~ Head rngs, Foo rngs) => FooData rngs +barWraper = bar + +bar :: (_) => FooData rngs +bar = foo + +data FooData rngs + +class Foo xs where foo :: (Head xs ~ '(r,r')) => FooData xs + +type family Head (xs :: [k]) where Head (x ': xs) = x + diff --git a/testsuite/tests/partial-sigs/should_compile/T12844.stderr b/testsuite/tests/partial-sigs/should_compile/T12844.stderr new file mode 100644 index 0000000..b7b9a71 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_compile/T12844.stderr @@ -0,0 +1,6 @@ + +T12844.hs:12:9: warning: [-Wpartial-type-signatures (in -Wdefault)] + Found constraint wildcard ‘_’ standing for ‘(Head rngs ~ '(r, r'), + Foo rngs)’ + In the type signature: + bar :: _ => FooData rngs diff --git a/testsuite/tests/partial-sigs/should_compile/all.T b/testsuite/tests/partial-sigs/should_compile/all.T index 3cec3e0..e5f266b 100644 --- a/testsuite/tests/partial-sigs/should_compile/all.T +++ b/testsuite/tests/partial-sigs/should_compile/all.T @@ -64,3 +64,4 @@ test('T11016', normal, compile, ['']) test('T11192', normal, compile, ['']) test('T12156', normal, compile_fail, ['-fdefer-typed-holes']) test('T12531', normal, compile, ['-fdefer-typed-holes']) +test('T12844', normal, compile, ['']) From git at git.haskell.org Fri Dec 2 16:01:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Dec 2016 16:01:01 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Tweaks to grammar and such. (cc84fd4) Message-ID: <20161202160101.BAD3C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/cc84fd48eadd9c1a7efc503e5f76215b82018f30/ghc >--------------------------------------------------------------- commit cc84fd48eadd9c1a7efc503e5f76215b82018f30 Author: Gabor Greif Date: Wed Nov 30 10:21:04 2016 +0100 Tweaks to grammar and such. (cherry picked from commit be8a47f5b7645f395543feb7c8779482a8f6d221) >--------------------------------------------------------------- cc84fd48eadd9c1a7efc503e5f76215b82018f30 docs/users_guide/8.0.2-notes.rst | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/docs/users_guide/8.0.2-notes.rst b/docs/users_guide/8.0.2-notes.rst index 063d947..9bc78ea 100644 --- a/docs/users_guide/8.0.2-notes.rst +++ b/docs/users_guide/8.0.2-notes.rst @@ -95,7 +95,7 @@ Compiler - A code generator bug which resulted in segmentation faults in compiled programs has been fixed (see :ghc-ticket:`12757`). -- GHC now supports systems whose C compiler which produce position-independent +- GHC now supports systems whose C compiler produces position-independent executables by default. (see :ghc-ticket:`12579`). - GHC can now be built on systems which use the ``gold`` linker by default @@ -108,8 +108,8 @@ Compiler - The :ghc-flag:`-Wredundant-constraints` flag has been removed from the :ghc-flag:`-Wall` flag set (see :ghc-ticket:`10635`). -- Added :ghc-flag:`-fdefer-out-of-scope-variables`, which converts variable - out of scope variables errors into warnings. +- Added :ghc-flag:`-fdefer-out-of-scope-variables`, which converts + out-of-scope variable errors into warnings. - The RTS :ghc-flag:`-xb` now reads the base heap address in any base, defaulting to decimal, hexadecimal if the address starts with ``0x``, and @@ -135,11 +135,11 @@ Runtime system ~~~~~~~~~~~~~~ - The Runtime linker on Windows is once again recognizing POSIX functions under their - "deprecated" name. e.g. "strdup" will now be recognizes and internally forwarded to "_strdup". + "deprecated" name. e.g. "strdup" will now be recognized and internally forwarded to "_strdup". If you have existing code already using the correct names (e.g. _strdup) then this will just continue to work and no change is needed. For more information about how the forwarding is done please see - `MSDN `_ . This should now introduce the same behavior - both compiled and interpreted. (see :ghc-ticket:`12497`). + `MSDN `_ . This should now introduce the same + behavior both compiled and interpreted. (see :ghc-ticket:`12497`). - Profiles from the cost-center profiler now provide source span information. (see :ghc-ticket:`11543`). From git at git.haskell.org Fri Dec 2 19:44:04 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Dec 2016 19:44:04 +0000 (UTC) Subject: [commit: ghc] master: Note Trac #12141 in mk/build.mk.sample (27731f1) Message-ID: <20161202194404.02AE43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/27731f144fb676d3117cd7e04eb71c13d53bb170/ghc >--------------------------------------------------------------- commit 27731f144fb676d3117cd7e04eb71c13d53bb170 Author: Ryan Scott Date: Fri Dec 2 14:40:23 2016 -0500 Note Trac #12141 in mk/build.mk.sample Mention that many GHC testsuite tests will fail with a compiler built with the quickest profile. See Trac #12141. >--------------------------------------------------------------- 27731f144fb676d3117cd7e04eb71c13d53bb170 mk/build.mk.sample | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/mk/build.mk.sample b/mk/build.mk.sample index eed749c..6266219 100644 --- a/mk/build.mk.sample +++ b/mk/build.mk.sample @@ -27,7 +27,8 @@ # Even faster build. NOT RECOMMENDED: the libraries will be # completely unoptimised, so any code built with this compiler -# (including stage2) will run very slowly: +# (including stage2) will run very slowly, and many GHC tests +# will fail with this profile (see Trac #12141): #BuildFlavour = quickest # Profile the stage2 compiler: From git at git.haskell.org Fri Dec 2 20:29:27 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Dec 2016 20:29:27 +0000 (UTC) Subject: [commit: ghc] master: fdReady: use poll() instead of select() (f46369b) Message-ID: <20161202202927.D2B873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f46369b8a1bf90a3bdc30f2b566c3a7e03672518/ghc >--------------------------------------------------------------- commit f46369b8a1bf90a3bdc30f2b566c3a7e03672518 Author: Simon Marlow Date: Fri Dec 2 14:32:24 2016 -0500 fdReady: use poll() instead of select() select() is limited to 1024 file descriptors. This actually blew up in a very hard-to-debug way in our production system when using the hinotify package. Test Plan: libraries/tests pass, paricularly hGetBuf001 which exercises this code. Reviewers: niteria, erikd, austin, hvr, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2785 GHC Trac Issues: #12912 >--------------------------------------------------------------- f46369b8a1bf90a3bdc30f2b566c3a7e03672518 libraries/base/cbits/inputReady.c | 42 ++++++++++++++++++++++++++++++--------- 1 file changed, 33 insertions(+), 9 deletions(-) diff --git a/libraries/base/cbits/inputReady.c b/libraries/base/cbits/inputReady.c index 8714eea..230e592 100644 --- a/libraries/base/cbits/inputReady.c +++ b/libraries/base/cbits/inputReady.c @@ -7,6 +7,9 @@ /* select and supporting types is not Posix */ /* #include "PosixSource.h" */ #include "HsBase.h" +#if !defined(_WIN32) +#include +#endif /* * inputReady(fd) checks to see whether input is available on the file @@ -16,19 +19,41 @@ int fdReady(int fd, int write, int msecs, int isSock) { - if -#if defined(_WIN32) - ( isSock ) { + +#if !defined(_WIN32) + + // We only handle msecs == 0 on non-Windows, because this is the + // only case we need. Non-zero waiting is handled by the IO manager. + if (msecs != 0) { + fprintf(stderr, "fdReady: msecs != 0, this shouldn't happen"); + abort(); + } + + struct pollfd fds[1]; + + fds[0].fd = fd; + fds[0].events = write ? POLLOUT : POLLIN; + fds[0].revents = 0; + + int res; + while ((res = poll(fds, 1, 0)) < 0) { + if (errno != EINTR) { + return (-1); + } + } + + // res is the number of FDs with events + return (res > 0); + #else - ( 1 ) { -#endif + + if (isSock) { int maxfd, ready; fd_set rfd, wfd; struct timeval tv; if ((fd >= (int)FD_SETSIZE) || (fd < 0)) { - /* avoid memory corruption on too large FDs */ - errno = EINVAL; - return -1; + fprintf(stderr, "fdReady: fd is too big"); + abort(); } FD_ZERO(&rfd); FD_ZERO(&wfd); @@ -54,7 +79,6 @@ fdReady(int fd, int write, int msecs, int isSock) /* 1 => Input ready, 0 => not ready, -1 => error */ return (ready); } -#if defined(_WIN32) else { DWORD rc; HANDLE hFile = (HANDLE)_get_osfhandle(fd); From git at git.haskell.org Fri Dec 2 20:29:31 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Dec 2016 20:29:31 +0000 (UTC) Subject: [commit: ghc] master: Install toplevel handler inside fork. (895a131) Message-ID: <20161202202931.2C0C53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/895a131f6e56847d9ebca2e9bfe19a3189e49d72/ghc >--------------------------------------------------------------- commit 895a131f6e56847d9ebca2e9bfe19a3189e49d72 Author: Alexander Vershilov Date: Fri Dec 2 14:32:48 2016 -0500 Install toplevel handler inside fork. When rts is forked it doesn't update toplevel handler, so UserInterrupt exception is sent to Thread1 that doesn't exist in forked process. We install toplevel handler when fork so signal will be delivered to the new main thread. Fixes #12903 Reviewers: simonmar, austin, erikd, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2770 GHC Trac Issues: #12903 >--------------------------------------------------------------- 895a131f6e56847d9ebca2e9bfe19a3189e49d72 includes/RtsAPI.h | 4 ++++ rts/Prelude.h | 2 ++ rts/RtsAPI.c | 29 +++++++++++++++++++++++++++++ rts/RtsSymbols.c | 1 + rts/Schedule.c | 5 ++++- rts/package.conf.in | 2 ++ testsuite/tests/rts/T12903.hs | 10 ++++++++++ testsuite/tests/rts/T12903.stdout | 1 + testsuite/tests/rts/all.T | 1 + 9 files changed, 54 insertions(+), 1 deletion(-) diff --git a/includes/RtsAPI.h b/includes/RtsAPI.h index 3b6e1dc..4dccb84 100644 --- a/includes/RtsAPI.h +++ b/includes/RtsAPI.h @@ -282,6 +282,10 @@ void rts_evalIO (/* inout */ Capability **, /* in */ HaskellObj p, /* out */ HaskellObj *ret); +void rts_evalStableIOMain (/* inout */ Capability **, + /* in */ HsStablePtr s, + /* out */ HsStablePtr *ret); + void rts_evalStableIO (/* inout */ Capability **, /* in */ HsStablePtr s, /* out */ HsStablePtr *ret); diff --git a/rts/Prelude.h b/rts/Prelude.h index 16881eb..0186b50 100644 --- a/rts/Prelude.h +++ b/rts/Prelude.h @@ -52,6 +52,7 @@ PRELUDE_CLOSURE(base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure); PRELUDE_CLOSURE(base_GHCziConcziSignal_runHandlersPtr_closure); PRELUDE_CLOSURE(base_GHCziTopHandler_flushStdHandles_closure); +PRELUDE_CLOSURE(base_GHCziTopHandler_runMainIO_closure); PRELUDE_INFO(ghczmprim_GHCziTypes_Czh_con_info); PRELUDE_INFO(ghczmprim_GHCziTypes_Izh_con_info); @@ -84,6 +85,7 @@ PRELUDE_INFO(base_GHCziStable_StablePtr_con_info); #define runHandlersPtr_closure DLL_IMPORT_DATA_REF(base_GHCziConcziSignal_runHandlersPtr_closure) #define flushStdHandles_closure DLL_IMPORT_DATA_REF(base_GHCziTopHandler_flushStdHandles_closure) +#define runMainIO_closure DLL_IMPORT_DATA_REF(base_GHCziTopHandler_runMainIO_closure) #define stackOverflow_closure DLL_IMPORT_DATA_REF(base_GHCziIOziException_stackOverflow_closure) #define heapOverflow_closure DLL_IMPORT_DATA_REF(base_GHCziIOziException_heapOverflow_closure) diff --git a/rts/RtsAPI.c b/rts/RtsAPI.c index f009de7..2ca5dc4 100644 --- a/rts/RtsAPI.c +++ b/rts/RtsAPI.c @@ -461,6 +461,35 @@ void rts_evalIO (/* inout */ Capability **cap, } /* + * rts_evalStableIOMain() is suitable for calling main Haskell thread + * stored in (StablePtr (IO a)) it calls rts_evalStableIO but wraps + * function in GHC.TopHandler.runMainIO that installs top_handlers. + * See Trac #12903. + */ +void rts_evalStableIOMain(/* inout */ Capability **cap, + /* in */ HsStablePtr s, + /* out */ HsStablePtr *ret) +{ + StgTSO* tso; + StgClosure *p, *r, *w; + SchedulerStatus stat; + + p = (StgClosure *)deRefStablePtr(s); + w = rts_apply(*cap, &base_GHCziTopHandler_runMainIO_closure, p); + tso = createStrictIOThread(*cap, RtsFlags.GcFlags.initialStkSize, w); + // async exceptions are always blocked by default in the created + // thread. See #1048. + tso->flags |= TSO_BLOCKEX | TSO_INTERRUPTIBLE; + scheduleWaitThread(tso,&r,cap); + stat = rts_getSchedStatus(*cap); + + if (stat == Success && ret != NULL) { + ASSERT(r != NULL); + *ret = getStablePtr((StgPtr)r); + } +} + +/* * rts_evalStableIO() is suitable for calling from Haskell. It * evaluates a value of the form (StablePtr (IO a)), forcing the * action's result to WHNF before returning. The result is returned diff --git a/rts/RtsSymbols.c b/rts/RtsSymbols.c index 60ffedb..e501596 100644 --- a/rts/RtsSymbols.c +++ b/rts/RtsSymbols.c @@ -666,6 +666,7 @@ SymI_HasProto(rts_eval) \ SymI_HasProto(rts_evalIO) \ SymI_HasProto(rts_evalLazyIO) \ + SymI_HasProto(rts_evalStableIOMain) \ SymI_HasProto(rts_evalStableIO) \ SymI_HasProto(rts_eval_) \ SymI_HasProto(rts_getBool) \ diff --git a/rts/Schedule.c b/rts/Schedule.c index 2c862af..49687b5 100644 --- a/rts/Schedule.c +++ b/rts/Schedule.c @@ -2103,7 +2103,10 @@ forkProcess(HsStablePtr *entry ioManagerStartCap(&cap); #endif - rts_evalStableIO(&cap, entry, NULL); // run the action + // Install toplevel exception handlers, so interruption + // signal will be sent to the main thread. + // See Trac #12903 + rts_evalStableIOMain(&cap, entry, NULL); // run the action rts_checkSchedStatus("forkProcess",cap); rts_unlock(cap); diff --git a/rts/package.conf.in b/rts/package.conf.in index 17d579f..1da44a4 100644 --- a/rts/package.conf.in +++ b/rts/package.conf.in @@ -104,6 +104,7 @@ ld-options: , "-Wl,-u,_base_GHCziTopHandler_flushStdHandles_closure" , "-Wl,-u,_base_GHCziTopHandler_runIO_closure" , "-Wl,-u,_base_GHCziTopHandler_runNonIO_closure" + , "-Wl,-u,_base_GHCziTopHandler_runMainIO_closure" , "-Wl,-u,_base_GHCziConcziIO_ensureIOManagerIsRunning_closure" , "-Wl,-u,_base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure" , "-Wl,-u,_base_GHCziConcziSync_runSparks_closure" @@ -195,6 +196,7 @@ ld-options: , "-Wl,-u,base_GHCziTopHandler_flushStdHandles_closure" , "-Wl,-u,base_GHCziTopHandler_runIO_closure" , "-Wl,-u,base_GHCziTopHandler_runNonIO_closure" + , "-Wl,-u,base_GHCziTopHandler_runMainIO_closure" , "-Wl,-u,base_GHCziConcziIO_ensureIOManagerIsRunning_closure" , "-Wl,-u,base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure" , "-Wl,-u,base_GHCziConcziSync_runSparks_closure" diff --git a/testsuite/tests/rts/T12903.hs b/testsuite/tests/rts/T12903.hs new file mode 100644 index 0000000..ddaf8b9 --- /dev/null +++ b/testsuite/tests/rts/T12903.hs @@ -0,0 +1,10 @@ +import Control.Concurrent +import Control.Exception +import System.Posix + +main = do + pid <- forkProcess $ do + handle (\UserInterrupt{} -> putStrLn "caught") + $ threadDelay 2000000 + signalProcess sigINT pid + threadDelay 2000000 diff --git a/testsuite/tests/rts/T12903.stdout b/testsuite/tests/rts/T12903.stdout new file mode 100644 index 0000000..cad99e1 --- /dev/null +++ b/testsuite/tests/rts/T12903.stdout @@ -0,0 +1 @@ +caught diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index 9c55b21..f9c4b8e 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -375,4 +375,5 @@ test('numa001', [ extra_run_opts('8'), extra_ways(['debug_numa']) ] test('T12497', [ unless(opsys('mingw32'), skip) ], run_command, ['$MAKE -s --no-print-directory T12497']) +test('T12903', [ when(opsys('mingw32'), skip)], compile_and_run, ['']) From git at git.haskell.org Fri Dec 2 20:29:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Dec 2016 20:29:34 +0000 (UTC) Subject: [commit: ghc] master: Maintain in-scope set in deeply_instantiate (fixes #12549). (2350906) Message-ID: <20161202202934.41A633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2350906bfb496758d81caf3b66b232e1950285e9/ghc >--------------------------------------------------------------- commit 2350906bfb496758d81caf3b66b232e1950285e9 Author: John Leo Date: Fri Dec 2 14:33:12 2016 -0500 Maintain in-scope set in deeply_instantiate (fixes #12549). Maintain in-scope set in deeply_instantiate (Fixes T12549). lint fixes Test Plan: validate Reviewers: simonpj, austin, goldfire, bgamari Reviewed By: simonpj, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2757 GHC Trac Issues: #12549 >--------------------------------------------------------------- 2350906bfb496758d81caf3b66b232e1950285e9 compiler/typecheck/Inst.hs | 34 ++++++++++++++++++++------- compiler/typecheck/TcMType.hs | 10 +++++++- testsuite/tests/ghci/should_run/T12549.script | 3 +++ testsuite/tests/ghci/should_run/T12549.stdout | 3 +++ testsuite/tests/ghci/should_run/all.T | 1 + 5 files changed, 42 insertions(+), 9 deletions(-) diff --git a/compiler/typecheck/Inst.hs b/compiler/typecheck/Inst.hs index 0a50de4..5015913 100644 --- a/compiler/typecheck/Inst.hs +++ b/compiler/typecheck/Inst.hs @@ -227,27 +227,45 @@ deeplyInstantiate :: CtOrigin -> TcSigmaType -> TcM (HsWrapper, TcRhoType) -- then wrap e :: rho -- That is, wrap :: ty ~> rho -deeplyInstantiate orig ty +deeplyInstantiate orig ty = + deeply_instantiate orig + (mkEmptyTCvSubst (mkInScopeSet (tyCoVarsOfType ty))) + ty + +deeply_instantiate :: CtOrigin + -> TCvSubst + -> TcSigmaType -> TcM (HsWrapper, TcRhoType) +-- Internal function to deeply instantiate that builds on an existing subst. +-- It extends the input substitution and applies the final subtitution to +-- the types on return. See #12549. + +deeply_instantiate orig subst ty | Just (arg_tys, tvs, theta, rho) <- tcDeepSplitSigmaTy_maybe ty - = do { (subst, tvs') <- newMetaTyVars tvs - ; ids1 <- newSysLocalIds (fsLit "di") (substTysUnchecked subst arg_tys) - ; let theta' = substThetaUnchecked subst theta + = do { (subst', tvs') <- newMetaTyVarsX subst tvs + ; ids1 <- newSysLocalIds (fsLit "di") (substTys subst' arg_tys) + ; let theta' = substTheta subst' theta ; wrap1 <- instCall orig (mkTyVarTys tvs') theta' ; traceTc "Instantiating (deeply)" (vcat [ text "origin" <+> pprCtOrigin orig , text "type" <+> ppr ty , text "with" <+> ppr tvs' , text "args:" <+> ppr ids1 , text "theta:" <+> ppr theta' - , text "subst:" <+> ppr subst ]) - ; (wrap2, rho2) <- deeplyInstantiate orig (substTyUnchecked subst rho) + , text "subst:" <+> ppr subst']) + ; (wrap2, rho2) <- deeply_instantiate orig subst' rho ; return (mkWpLams ids1 <.> wrap2 <.> wrap1 <.> mkWpEvVarApps ids1, mkFunTys arg_tys rho2) } - | otherwise = return (idHsWrapper, ty) - + | otherwise + = do { let ty' = substTy subst ty + ; traceTc "deeply_instantiate final subst" + (vcat [ text "origin:" <+> pprCtOrigin orig + , text "type:" <+> ppr ty + , text "new type:" <+> ppr ty' + , text "subst:" <+> ppr subst ]) + ; return (idHsWrapper, ty') } {- ************************************************************************ diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index b5104a1..2e9a7a7 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -53,7 +53,7 @@ module TcMType ( -------------------------------- -- Instantiation - newMetaTyVars, newMetaTyVarX, + newMetaTyVars, newMetaTyVarX, newMetaTyVarsX, newMetaSigTyVars, newMetaSigTyVarX, newSigTyVar, newWildCardX, tcInstType, @@ -811,6 +811,10 @@ newMetaTyVarX :: TCvSubst -> TyVar -> TcM (TCvSubst, TcTyVar) -- an existing TyVar. We substitute kind variables in the kind. newMetaTyVarX subst tyvar = new_meta_tv_x TauTv subst tyvar +newMetaTyVarsX :: TCvSubst -> [TyVar] -> TcM (TCvSubst, [TcTyVar]) +-- Just like newMetaTyVars, but start with an existing substitution. +newMetaTyVarsX subst = mapAccumLM newMetaTyVarX subst + newMetaSigTyVarX :: TCvSubst -> TyVar -> TcM (TCvSubst, TcTyVar) -- Just like newMetaTyVarX, but make a SigTv newMetaSigTyVarX subst tyvar = new_meta_tv_x SigTv subst tyvar @@ -827,6 +831,10 @@ new_meta_tv_x info subst tv ; let name = mkSystemName uniq (getOccName tv) -- See Note [Name of an instantiated type variable] kind = substTyUnchecked subst (tyVarKind tv) + -- NOTE: Trac #12549 is fixed so we could use + -- substTy here, but the tc_infer_args problem + -- is not yet fixed so leaving as unchecked for now. + -- OLD NOTE: -- Unchecked because we call newMetaTyVarX from -- tcInstBinderX, which is called from tc_infer_args -- which does not yet take enough trouble to ensure diff --git a/testsuite/tests/ghci/should_run/T12549.script b/testsuite/tests/ghci/should_run/T12549.script new file mode 100644 index 0000000..012517f --- /dev/null +++ b/testsuite/tests/ghci/should_run/T12549.script @@ -0,0 +1,3 @@ +:set -XPolyKinds +class C a where f :: a b c +:t f diff --git a/testsuite/tests/ghci/should_run/T12549.stdout b/testsuite/tests/ghci/should_run/T12549.stdout new file mode 100644 index 0000000..fd0a45c --- /dev/null +++ b/testsuite/tests/ghci/should_run/T12549.stdout @@ -0,0 +1,3 @@ +f :: forall k1 k2 (b :: k1) (a :: k1 -> k2 -> *) (c :: k2). + C a => + a b c diff --git a/testsuite/tests/ghci/should_run/all.T b/testsuite/tests/ghci/should_run/all.T index b6aa2e9..3dc05ce 100644 --- a/testsuite/tests/ghci/should_run/all.T +++ b/testsuite/tests/ghci/should_run/all.T @@ -26,3 +26,4 @@ test('T11328', just_ghci, ghci_script, ['T11328.script']) test('T11825', just_ghci, ghci_script, ['T11825.script']) test('T12128', just_ghci, ghci_script, ['T12128.script']) test('T12456', just_ghci, ghci_script, ['T12456.script']) +test('T12549', just_ghci, ghci_script, ['T12549.script']) From git at git.haskell.org Fri Dec 2 21:09:23 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Dec 2016 21:09:23 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: fdReady: use poll() instead of select() (d9e7a69) Message-ID: <20161202210923.1F98E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/d9e7a69290c39f6075b70c218fbcf7f85682e9cb/ghc >--------------------------------------------------------------- commit d9e7a69290c39f6075b70c218fbcf7f85682e9cb Author: Simon Marlow Date: Fri Dec 2 14:32:24 2016 -0500 fdReady: use poll() instead of select() select() is limited to 1024 file descriptors. This actually blew up in a very hard-to-debug way in our production system when using the hinotify package. Test Plan: libraries/tests pass, paricularly hGetBuf001 which exercises this code. Reviewers: niteria, erikd, austin, hvr, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2785 GHC Trac Issues: #12912 (cherry picked from commit f46369b8a1bf90a3bdc30f2b566c3a7e03672518) >--------------------------------------------------------------- d9e7a69290c39f6075b70c218fbcf7f85682e9cb libraries/base/cbits/inputReady.c | 42 ++++++++++++++++++++++++++++++--------- 1 file changed, 33 insertions(+), 9 deletions(-) diff --git a/libraries/base/cbits/inputReady.c b/libraries/base/cbits/inputReady.c index 8714eea..230e592 100644 --- a/libraries/base/cbits/inputReady.c +++ b/libraries/base/cbits/inputReady.c @@ -7,6 +7,9 @@ /* select and supporting types is not Posix */ /* #include "PosixSource.h" */ #include "HsBase.h" +#if !defined(_WIN32) +#include +#endif /* * inputReady(fd) checks to see whether input is available on the file @@ -16,19 +19,41 @@ int fdReady(int fd, int write, int msecs, int isSock) { - if -#if defined(_WIN32) - ( isSock ) { + +#if !defined(_WIN32) + + // We only handle msecs == 0 on non-Windows, because this is the + // only case we need. Non-zero waiting is handled by the IO manager. + if (msecs != 0) { + fprintf(stderr, "fdReady: msecs != 0, this shouldn't happen"); + abort(); + } + + struct pollfd fds[1]; + + fds[0].fd = fd; + fds[0].events = write ? POLLOUT : POLLIN; + fds[0].revents = 0; + + int res; + while ((res = poll(fds, 1, 0)) < 0) { + if (errno != EINTR) { + return (-1); + } + } + + // res is the number of FDs with events + return (res > 0); + #else - ( 1 ) { -#endif + + if (isSock) { int maxfd, ready; fd_set rfd, wfd; struct timeval tv; if ((fd >= (int)FD_SETSIZE) || (fd < 0)) { - /* avoid memory corruption on too large FDs */ - errno = EINVAL; - return -1; + fprintf(stderr, "fdReady: fd is too big"); + abort(); } FD_ZERO(&rfd); FD_ZERO(&wfd); @@ -54,7 +79,6 @@ fdReady(int fd, int write, int msecs, int isSock) /* 1 => Input ready, 0 => not ready, -1 => error */ return (ready); } -#if defined(_WIN32) else { DWORD rc; HANDLE hFile = (HANDLE)_get_osfhandle(fd); From git at git.haskell.org Fri Dec 2 21:09:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Dec 2016 21:09:26 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Install toplevel handler inside fork. (fb0f4cf) Message-ID: <20161202210926.5B3173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/fb0f4cf66f3fc7590821e6688440bf86c25aced1/ghc >--------------------------------------------------------------- commit fb0f4cf66f3fc7590821e6688440bf86c25aced1 Author: Alexander Vershilov Date: Fri Dec 2 14:32:48 2016 -0500 Install toplevel handler inside fork. When rts is forked it doesn't update toplevel handler, so UserInterrupt exception is sent to Thread1 that doesn't exist in forked process. We install toplevel handler when fork so signal will be delivered to the new main thread. Fixes #12903 Reviewers: simonmar, austin, erikd, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2770 GHC Trac Issues: #12903 (cherry picked from commit 895a131f6e56847d9ebca2e9bfe19a3189e49d72) >--------------------------------------------------------------- fb0f4cf66f3fc7590821e6688440bf86c25aced1 includes/RtsAPI.h | 4 ++++ rts/Prelude.h | 2 ++ rts/RtsAPI.c | 29 +++++++++++++++++++++++++++++ rts/RtsSymbols.c | 1 + rts/Schedule.c | 5 ++++- rts/package.conf.in | 2 ++ testsuite/tests/rts/T12903.hs | 10 ++++++++++ testsuite/tests/rts/T12903.stdout | 1 + testsuite/tests/rts/all.T | 2 ++ 9 files changed, 55 insertions(+), 1 deletion(-) diff --git a/includes/RtsAPI.h b/includes/RtsAPI.h index 4748060..0e29c63 100644 --- a/includes/RtsAPI.h +++ b/includes/RtsAPI.h @@ -245,6 +245,10 @@ void rts_evalIO (/* inout */ Capability **, /* in */ HaskellObj p, /* out */ HaskellObj *ret); +void rts_evalStableIOMain (/* inout */ Capability **, + /* in */ HsStablePtr s, + /* out */ HsStablePtr *ret); + void rts_evalStableIO (/* inout */ Capability **, /* in */ HsStablePtr s, /* out */ HsStablePtr *ret); diff --git a/rts/Prelude.h b/rts/Prelude.h index ae1e9cb..444aa46 100644 --- a/rts/Prelude.h +++ b/rts/Prelude.h @@ -51,6 +51,7 @@ PRELUDE_CLOSURE(base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure); PRELUDE_CLOSURE(base_GHCziConcziSignal_runHandlersPtr_closure); PRELUDE_CLOSURE(base_GHCziTopHandler_flushStdHandles_closure); +PRELUDE_CLOSURE(base_GHCziTopHandler_runMainIO_closure); PRELUDE_INFO(ghczmprim_GHCziTypes_Czh_static_info); PRELUDE_INFO(ghczmprim_GHCziTypes_Izh_static_info); @@ -99,6 +100,7 @@ PRELUDE_INFO(base_GHCziStable_StablePtr_con_info); #define runHandlersPtr_closure DLL_IMPORT_DATA_REF(base_GHCziConcziSignal_runHandlersPtr_closure) #define flushStdHandles_closure DLL_IMPORT_DATA_REF(base_GHCziTopHandler_flushStdHandles_closure) +#define runMainIO_closure DLL_IMPORT_DATA_REF(base_GHCziTopHandler_runMainIO_closure) #define stackOverflow_closure DLL_IMPORT_DATA_REF(base_GHCziIOziException_stackOverflow_closure) #define heapOverflow_closure DLL_IMPORT_DATA_REF(base_GHCziIOziException_heapOverflow_closure) diff --git a/rts/RtsAPI.c b/rts/RtsAPI.c index c64d8af..47f6c93 100644 --- a/rts/RtsAPI.c +++ b/rts/RtsAPI.c @@ -460,6 +460,35 @@ void rts_evalIO (/* inout */ Capability **cap, } /* + * rts_evalStableIOMain() is suitable for calling main Haskell thread + * stored in (StablePtr (IO a)) it calls rts_evalStableIO but wraps + * function in GHC.TopHandler.runMainIO that installs top_handlers. + * See Trac #12903. + */ +void rts_evalStableIOMain(/* inout */ Capability **cap, + /* in */ HsStablePtr s, + /* out */ HsStablePtr *ret) +{ + StgTSO* tso; + StgClosure *p, *r, *w; + SchedulerStatus stat; + + p = (StgClosure *)deRefStablePtr(s); + w = rts_apply(*cap, &base_GHCziTopHandler_runMainIO_closure, p); + tso = createStrictIOThread(*cap, RtsFlags.GcFlags.initialStkSize, w); + // async exceptions are always blocked by default in the created + // thread. See #1048. + tso->flags |= TSO_BLOCKEX | TSO_INTERRUPTIBLE; + scheduleWaitThread(tso,&r,cap); + stat = rts_getSchedStatus(*cap); + + if (stat == Success && ret != NULL) { + ASSERT(r != NULL); + *ret = getStablePtr((StgPtr)r); + } +} + +/* * rts_evalStableIO() is suitable for calling from Haskell. It * evaluates a value of the form (StablePtr (IO a)), forcing the * action's result to WHNF before returning. The result is returned diff --git a/rts/RtsSymbols.c b/rts/RtsSymbols.c index fec5cfc..44b6591 100644 --- a/rts/RtsSymbols.c +++ b/rts/RtsSymbols.c @@ -647,6 +647,7 @@ SymI_HasProto(rts_eval) \ SymI_HasProto(rts_evalIO) \ SymI_HasProto(rts_evalLazyIO) \ + SymI_HasProto(rts_evalStableIOMain) \ SymI_HasProto(rts_evalStableIO) \ SymI_HasProto(rts_eval_) \ SymI_HasProto(rts_getBool) \ diff --git a/rts/Schedule.c b/rts/Schedule.c index 1f42e42..33599d0 100644 --- a/rts/Schedule.c +++ b/rts/Schedule.c @@ -2078,7 +2078,10 @@ forkProcess(HsStablePtr *entry ioManagerStartCap(&cap); #endif - rts_evalStableIO(&cap, entry, NULL); // run the action + // Install toplevel exception handlers, so interruption + // signal will be sent to the main thread. + // See Trac #12903 + rts_evalStableIOMain(&cap, entry, NULL); // run the action rts_checkSchedStatus("forkProcess",cap); rts_unlock(cap); diff --git a/rts/package.conf.in b/rts/package.conf.in index c0256bb..e328be7 100644 --- a/rts/package.conf.in +++ b/rts/package.conf.in @@ -106,6 +106,7 @@ ld-options: , "-Wl,-u,_base_GHCziTopHandler_flushStdHandles_closure" , "-Wl,-u,_base_GHCziTopHandler_runIO_closure" , "-Wl,-u,_base_GHCziTopHandler_runNonIO_closure" + , "-Wl,-u,_base_GHCziTopHandler_runMainIO_closure" , "-Wl,-u,_base_GHCziConcziIO_ensureIOManagerIsRunning_closure" , "-Wl,-u,_base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure" , "-Wl,-u,_base_GHCziConcziSync_runSparks_closure" @@ -148,6 +149,7 @@ ld-options: , "-Wl,-u,base_GHCziTopHandler_flushStdHandles_closure" , "-Wl,-u,base_GHCziTopHandler_runIO_closure" , "-Wl,-u,base_GHCziTopHandler_runNonIO_closure" + , "-Wl,-u,base_GHCziTopHandler_runMainIO_closure" , "-Wl,-u,base_GHCziConcziIO_ensureIOManagerIsRunning_closure" , "-Wl,-u,base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure" , "-Wl,-u,base_GHCziConcziSync_runSparks_closure" diff --git a/testsuite/tests/rts/T12903.hs b/testsuite/tests/rts/T12903.hs new file mode 100644 index 0000000..ddaf8b9 --- /dev/null +++ b/testsuite/tests/rts/T12903.hs @@ -0,0 +1,10 @@ +import Control.Concurrent +import Control.Exception +import System.Posix + +main = do + pid <- forkProcess $ do + handle (\UserInterrupt{} -> putStrLn "caught") + $ threadDelay 2000000 + signalProcess sigINT pid + threadDelay 2000000 diff --git a/testsuite/tests/rts/T12903.stdout b/testsuite/tests/rts/T12903.stdout new file mode 100644 index 0000000..cad99e1 --- /dev/null +++ b/testsuite/tests/rts/T12903.stdout @@ -0,0 +1 @@ +caught diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index f7d518c..d889276 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -345,3 +345,5 @@ test('T10296b', [only_ways('threaded2')], compile_and_run, ['']) test('T12497', [ unless(opsys('mingw32'), skip) ], run_command, ['$MAKE -s --no-print-directory T12497']) +test('T12903', [ when(opsys('mingw32'), skip)], compile_and_run, ['']) + From git at git.haskell.org Fri Dec 2 22:16:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Dec 2016 22:16:01 +0000 (UTC) Subject: [commit: ghc] master: 8.2.1-notes.rst: tweak binutils version (eb6f673) Message-ID: <20161202221601.6A3F13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eb6f6730d2e80ba3b0c7468c11fd2c838e56a417/ghc >--------------------------------------------------------------- commit eb6f6730d2e80ba3b0c7468c11fd2c838e56a417 Author: Sergei Trofimovich Date: Fri Dec 2 22:14:23 2016 +0000 8.2.1-notes.rst: tweak binutils version It's 2.27 (-2), not 1.27.2. Dropped stray '\r'. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- eb6f6730d2e80ba3b0c7468c11fd2c838e56a417 docs/users_guide/8.2.1-notes.rst | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index 70b1f80..42a1ded 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -98,7 +98,7 @@ Compiler data TSyn = (T :: (forall k. k -> Type) -> Type) - The Mingw-w64 toolchain for the Windows version of GHC has been updated. GHC now uses - `GCC 6.2.0` and `binutils 1.27.2`. + `GCC 6.2.0` and `binutils 2.27`. GHCi ~~~~ From git at git.haskell.org Fri Dec 2 23:14:20 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Dec 2016 23:14:20 +0000 (UTC) Subject: [commit: ghc] master: core-spec: Fix S_MatchData (90c5af4) Message-ID: <20161202231420.2CE023A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/90c5af4778c8ed1c33991c4f28bbbe8958f1e60f/ghc >--------------------------------------------------------------- commit 90c5af4778c8ed1c33991c4f28bbbe8958f1e60f Author: Joachim Breitner Date: Fri Dec 2 18:13:03 2016 -0500 core-spec: Fix S_MatchData Previously, it would substitute e for n without an e being around. I clarify that by naming the scrutinee e. >--------------------------------------------------------------- 90c5af4778c8ed1c33991c4f28bbbe8958f1e60f docs/core-spec/OpSem.ott | 3 ++- docs/core-spec/core-spec.pdf | Bin 348408 -> 348416 bytes 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/docs/core-spec/OpSem.ott b/docs/core-spec/OpSem.ott index db8ce1c..b833b74 100644 --- a/docs/core-spec/OpSem.ott +++ b/docs/core-spec/OpSem.ott @@ -66,9 +66,10 @@ S |- e --> e' S |- case e as n return t of --> case e' as n return t of altj = K -> u +e = K u' = u[n |-> e] sbb] // bb /> ecc] // cc /> -------------------------------------------------------------- :: MatchData -S |- case K as n return t of --> u' +S |- case e as n return t of --> u' altj = lit -> u ---------------------------------------------------------------- :: MatchLit diff --git a/docs/core-spec/core-spec.pdf b/docs/core-spec/core-spec.pdf index ac548f6..a06ffd0 100644 Binary files a/docs/core-spec/core-spec.pdf and b/docs/core-spec/core-spec.pdf differ From git at git.haskell.org Mon Dec 5 17:40:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Dec 2016 17:40:26 +0000 (UTC) Subject: [commit: ghc] master: Fix an asymptotic bug in the occurrence analyser (517d03e) Message-ID: <20161205174026.E13453A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/517d03e41b4f5c144d1ad684539340421be2be2a/ghc >--------------------------------------------------------------- commit 517d03e41b4f5c144d1ad684539340421be2be2a Author: Simon Peyton Jones Date: Fri Dec 2 13:59:11 2016 +0000 Fix an asymptotic bug in the occurrence analyser Trac #12425 and #12234 showed up a major and long-standing bug in the occurrence analyser, whereby it could generate explonentially large program! There's a lot of commentary on #12425; and it's all described in Note [Loop breakers, node scoring, and stability] I did quite a lot of refactoring to make the code comprehensibe again (its structure had bit-rotted rather), so the patch looks bigger than it really is. Hurrah! I did a nofib run to check that I hadn't inadertently ruined anything: -------------------------------------------------------------------------------- Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- fluid -0.3% -1.5% 0.01 0.01 +0.0% parser -0.9% +0.6% 0.04 0.04 +0.0% prolog -0.1% +1.2% 0.00 0.00 +0.0% -------------------------------------------------------------------------------- Min -0.9% -1.5% -8.6% -8.7% +0.0% Max +0.1% +1.2% +7.7% +7.8% +2.4% Geometric Mean -0.2% -0.0% -0.2% -0.3% +0.0% I checked what happened in 'prolog'. It seems that we have a recursive data structure something like this f :: [blah] f x = build (\cn. ...g... ) g :: [blah2] g y = ....(foldr k z (f y)).... If we inline 'f' into 'g' we get better fusion than the other way round, but we don't have any way to spot that at the moment. (I wonder if we could do worker/wrapper for functions returning a 'build'?) It was happening before by a fluke. Anyway I decided to accept this; it's relatively rare I think. >--------------------------------------------------------------- 517d03e41b4f5c144d1ad684539340421be2be2a compiler/coreSyn/CoreSyn.hs | 14 +- compiler/simplCore/OccurAnal.hs | 740 +++++++++++++-------- testsuite/tests/perf/compiler/T12234.hs | 14 + testsuite/tests/perf/compiler/T12425.hs | 31 + testsuite/tests/perf/compiler/all.T | 21 + .../tests/simplCore/should_compile/T8848.stderr | 10 +- testsuite/tests/typecheck/should_compile/all.T | 1 + 7 files changed, 547 insertions(+), 284 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 517d03e41b4f5c144d1ad684539340421be2be2a From git at git.haskell.org Mon Dec 5 17:40:30 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Dec 2016 17:40:30 +0000 (UTC) Subject: [commit: ghc] master: Fix used-variable calculation (Trac #12548) (6305674) Message-ID: <20161205174030.70ECB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6305674f310633d159a4df4e2e0d033a698599d1/ghc >--------------------------------------------------------------- commit 6305674f310633d159a4df4e2e0d033a698599d1 Author: Simon Peyton Jones Date: Mon Dec 5 13:17:35 2016 +0000 Fix used-variable calculation (Trac #12548) The used-variable calculation for pattern synonyms is a little tricky, for reasons described in RnBinds Note [Pattern synonym builders don't yield dependencies] It was right semantically, but the "unused-variable warning" was wrong, which led to Trac #12548. >--------------------------------------------------------------- 6305674f310633d159a4df4e2e0d033a698599d1 compiler/hsSyn/HsUtils.hs | 8 ++++- compiler/rename/RnBinds.hs | 48 ++++++++++++++++--------- compiler/typecheck/TcBinds.hs | 1 + compiler/typecheck/TcEnv.hs | 9 +---- testsuite/tests/rename/should_compile/T12548.hs | 12 +++++++ testsuite/tests/rename/should_compile/all.T | 1 + 6 files changed, 54 insertions(+), 25 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6305674f310633d159a4df4e2e0d033a698599d1 From git at git.haskell.org Mon Dec 5 17:40:33 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Dec 2016 17:40:33 +0000 (UTC) Subject: [commit: ghc] master: Use isFamFreeTyCon now we have it (e912310) Message-ID: <20161205174033.2706F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e912310206e86169c920319f587d310c8b9cafe0/ghc >--------------------------------------------------------------- commit e912310206e86169c920319f587d310c8b9cafe0 Author: Simon Peyton Jones Date: Mon Dec 5 13:50:48 2016 +0000 Use isFamFreeTyCon now we have it Refactoring only >--------------------------------------------------------------- e912310206e86169c920319f587d310c8b9cafe0 compiler/typecheck/TcFlatten.hs | 12 ++++-------- compiler/types/TyCon.hs | 2 +- testsuite/tests/perf/compiler/all.T | 4 +++- 3 files changed, 8 insertions(+), 10 deletions(-) diff --git a/compiler/typecheck/TcFlatten.hs b/compiler/typecheck/TcFlatten.hs index 94fdfb8..700412b 100644 --- a/compiler/typecheck/TcFlatten.hs +++ b/compiler/typecheck/TcFlatten.hs @@ -19,7 +19,6 @@ import TyCoRep -- performs delicate algorithm on types import Coercion import Var import VarEnv -import NameEnv import Outputable import TcSMonad as TcS import BasicTypes( SwapFlag(..) ) @@ -895,19 +894,16 @@ flatten_one (AppTy ty1 ty2) role2 co2 xi2 ty2 role1 ) } -- output should match fmode -flatten_one ty@(TyConApp tc tys) +flatten_one (TyConApp tc tys) -- Expand type synonyms that mention type families -- on the RHS; see Note [Flattening synonyms] | Just (tenv, rhs, tys') <- expandSynTyCon_maybe tc tys , let expanded_ty = mkAppTys (substTy (mkTvSubstPrs tenv) rhs) tys' = do { mode <- getMode - ; let used_tcs = tyConsOfType rhs ; case mode of - FM_FlattenAll | anyNameEnv isTypeFamilyTyCon used_tcs - -> do { traceFlat "flatten_one syn expand" (ppr ty $$ ppr used_tcs) - ; flatten_one expanded_ty } - _ -> do { traceFlat "flatten_one syn no expand" (ppr ty) - ; flatten_ty_con_app tc tys } } + FM_FlattenAll | not (isFamFreeTyCon tc) + -> flatten_one expanded_ty + _ -> flatten_ty_con_app tc tys } -- Otherwise, it's a type function application, and we have to -- flatten it away as well, and generate a new given equality constraint diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index ebb18f0..ec2f5d5 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -627,7 +627,7 @@ data TyCon synIsTau :: Bool, -- True <=> the RHS of this synonym does not -- have any foralls, after expanding any -- nested synonyms - synIsFamFree :: Bool -- True <=> the RHS of this synonym does mention + synIsFamFree :: Bool -- True <=> the RHS of this synonym does not mention -- any type synonym families (data families -- are fine), again after expanding any -- nested synonyms diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 7ce6562..0ccde15 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -767,7 +767,7 @@ test('T9872c', test('T9872d', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 506691240, 5), + [(wordsize(64), 478169352, 5), # 2014-12-18 796071864 Initally created # 2014-12-18 739189056 Reduce type families even more eagerly # 2015-01-07 687562440 TrieMap leaf compression @@ -775,6 +775,8 @@ test('T9872d', # 2015-12-11 566134504 TypeInType; see #11196 # 2016-02-08 534693648 Improved a bit by tyConRolesRepresentational # 2016-03-18 506691240 optimize Unify & zonking + # 2016-12-05 478169352 using tyConIsTyFamFree, I think, but only + # a 1% improvement 482 -> 478 (wordsize(32), 264566040, 5) # some date 328810212 # 2015-07-11 350369584 From git at git.haskell.org Mon Dec 5 17:40:36 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Dec 2016 17:40:36 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #12925 (3e3f7c2) Message-ID: <20161205174036.5B40A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3e3f7c21a64758c671192c63a741ecc4a5a08831/ghc >--------------------------------------------------------------- commit 3e3f7c21a64758c671192c63a741ecc4a5a08831 Author: Simon Peyton Jones Date: Mon Dec 5 17:18:19 2016 +0000 Test Trac #12925 >--------------------------------------------------------------- 3e3f7c21a64758c671192c63a741ecc4a5a08831 testsuite/tests/typecheck/should_compile/T12925.hs | 12 ++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 2 +- 2 files changed, 13 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/typecheck/should_compile/T12925.hs b/testsuite/tests/typecheck/should_compile/T12925.hs new file mode 100644 index 0000000..986aa51 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T12925.hs @@ -0,0 +1,12 @@ +module Bug where + +data Foo a x = Foo x + +refoo :: Foo a x -> Foo b x +{-# NOINLINE refoo #-} +refoo (Foo x) = Foo x + +{-# RULES + +"refoo/refoo" forall s. + refoo (refoo s) = s #-} diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index de7f147..e2d65bd 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -555,4 +555,4 @@ test('T12734', normal, compile, ['']) test('T12734a', normal, compile_fail, ['']) test('T12763', normal, compile, ['']) test('T12797', normal, compile, ['']) - +test('T12925', normal, compile, ['']) From git at git.haskell.org Mon Dec 5 20:51:44 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Dec 2016 20:51:44 +0000 (UTC) Subject: [commit: ghc] master: Color output is wreaking havoc on test results (847d229) Message-ID: <20161205205144.F2EDD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/847d229346431483b99adcff12e46c7bf6af15da/ghc >--------------------------------------------------------------- commit 847d229346431483b99adcff12e46c7bf6af15da Author: Tamar Christina Date: Mon Dec 5 20:51:11 2016 +0000 Color output is wreaking havoc on test results Summary: D2716 introduced colors into the output of GHC. These color ourputs are done using escape characters output to the terminal. These however are wreaking havoc on the testsuite output as now no stderr with a warning or error will match anymore. Instead of accepting the new codes as expected values instead I turn them off. So the testsuite is consistent on platforms/terminals we don't support colors on. Test Plan: any test that outputs colors. e.g. make test TEST=T9576 Reviewers: austin, Rufflewind, bgamari Subscribers: thomie, #ghc_windows_task_force Differential Revision: https://phabricator.haskell.org/D2787 GHC Trac Issues: #8809 >--------------------------------------------------------------- 847d229346431483b99adcff12e46c7bf6af15da testsuite/mk/ghc-config.hs | 6 ++++++ testsuite/mk/test.mk | 6 ++++++ 2 files changed, 12 insertions(+) diff --git a/testsuite/mk/ghc-config.hs b/testsuite/mk/ghc-config.hs index 84f1523..cf55008 100644 --- a/testsuite/mk/ghc-config.hs +++ b/testsuite/mk/ghc-config.hs @@ -42,6 +42,12 @@ main = do _ -> "NO" putStrLn $ "MinGhcVersion711" ++ '=':minGhcVersion711 + let minGhcVersion801 = case lookup "Project version" fields of + Just v + | parseVersion v >= [8,1] -> "YES" + _ -> "NO" + putStrLn $ "MinGhcVersion801" ++ '=':minGhcVersion801 + getGhcFieldOrFail :: [(String,String)] -> String -> String -> IO () getGhcFieldOrFail fields mkvar key diff --git a/testsuite/mk/test.mk b/testsuite/mk/test.mk index d4bd5fe..16be955 100644 --- a/testsuite/mk/test.mk +++ b/testsuite/mk/test.mk @@ -43,6 +43,12 @@ TEST_HC_OPTS += -fno-warn-missed-specialisations TEST_HC_OPTS += -fshow-warning-groups endif +ifeq "$(MinGhcVersion801)" "YES" +# Turn off any VT800 codes in the output or they wreak havoc on the +# testsuite output. +TEST_HC_OPTS += -fdiagnostics-color=never +endif + # Add the no-debug-output last as it is often convenient to copy the test invocation # removing this line. TEST_HC_OPTS += -dno-debug-output From git at git.haskell.org Tue Dec 6 07:01:35 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Dec 2016 07:01:35 +0000 (UTC) Subject: [commit: ghc] master: Fix x86 Windows build and testsuite (b82f71b) Message-ID: <20161206070135.2ACD93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b82f71b96660400b4b9fa7f3ccef9df7532bb2d7/ghc >--------------------------------------------------------------- commit b82f71b96660400b4b9fa7f3ccef9df7532bb2d7 Author: Tamar Christina Date: Mon Dec 5 21:27:23 2016 +0000 Fix x86 Windows build and testsuite Summary: Fix issues preventing x86 GHC to build on Windows and fix segfault in the testsuite. Test Plan: ./validate Reviewers: austin, erikd, simonmar, bgamari Reviewed By: bgamari Subscribers: #ghc_windows_task_force, thomie Differential Revision: https://phabricator.haskell.org/D2789 >--------------------------------------------------------------- b82f71b96660400b4b9fa7f3ccef9df7532bb2d7 rts/linker/PEi386.c | 2 ++ rts/posix/OSMem.c | 2 +- rts/sm/OSMem.h | 2 +- rts/win32/OSMem.c | 6 +++--- rts/win32/OSThreads.c | 18 +++++++++--------- testsuite/timeout/WinCBindings.hsc | 3 ++- 6 files changed, 18 insertions(+), 15 deletions(-) diff --git a/rts/linker/PEi386.c b/rts/linker/PEi386.c index 5eaa35a..b7db10b 100644 --- a/rts/linker/PEi386.c +++ b/rts/linker/PEi386.c @@ -68,10 +68,12 @@ static UChar *cstring_from_COFF_symbol_name( UChar* name, UChar* strtab); +#if defined(x86_64_HOST_ARCH) static size_t makeSymbolExtra_PEi386( ObjectCode* oc, size_t s, char* symbol); +#endif static void addDLLHandle( pathchar* dll_name, diff --git a/rts/posix/OSMem.c b/rts/posix/OSMem.c index beffeda..dcf734f 100644 --- a/rts/posix/OSMem.c +++ b/rts/posix/OSMem.c @@ -593,7 +593,7 @@ uint32_t osNumaNodes(void) #endif } -StgWord osNumaMask(void) +uint64_t osNumaMask(void) { #if HAVE_LIBNUMA struct bitmask *mask; diff --git a/rts/sm/OSMem.h b/rts/sm/OSMem.h index f6f9559..4d158df 100644 --- a/rts/sm/OSMem.h +++ b/rts/sm/OSMem.h @@ -21,7 +21,7 @@ StgWord64 getPhysicalMemorySize (void); void setExecutable (void *p, W_ len, bool exec); bool osNumaAvailable(void); uint32_t osNumaNodes(void); -StgWord osNumaMask(void); +uint64_t osNumaMask(void); void osBindMBlocksToNode(void *addr, StgWord size, uint32_t node); INLINE_HEADER size_t diff --git a/rts/win32/OSMem.c b/rts/win32/OSMem.c index b6b97a7..2a54235 100644 --- a/rts/win32/OSMem.c +++ b/rts/win32/OSMem.c @@ -518,9 +518,9 @@ uint32_t osNumaNodes(void) return numNumaNodes; } -StgWord osNumaMask(void) +uint64_t osNumaMask(void) { - StgWord numaMask; + uint64_t numaMask; if (!GetNumaNodeProcessorMask(0, &numaMask)) { return 1; @@ -561,7 +561,7 @@ void osBindMBlocksToNode( } else { sysErrorBelch( - "osBindMBlocksToNode: VirtualAllocExNuma MEM_RESERVE %llu bytes " + "osBindMBlocksToNode: VirtualAllocExNuma MEM_RESERVE %" FMT_Word " bytes " "at address %p bytes failed", size, addr); } diff --git a/rts/win32/OSThreads.c b/rts/win32/OSThreads.c index 652ba13..d2f867c 100644 --- a/rts/win32/OSThreads.c +++ b/rts/win32/OSThreads.c @@ -328,6 +328,7 @@ getNumberOfProcessorsGroups (void) return n_groups; } +#if x86_64_HOST_ARCH static uint8_t* getProcessorsDistribution (void) { @@ -342,7 +343,6 @@ getProcessorsDistribution (void) cpuGroupDistCache = malloc(n_groups * sizeof(uint8_t)); memset(cpuGroupDistCache, MAXIMUM_PROCESSORS, n_groups * sizeof(uint8_t)); -#if x86_64_HOST_ARCH /* We still support Windows Vista. Which means we can't rely on the API being available. So we'll have to resolve manually. */ HMODULE kernel = GetModuleHandleW(L"kernel32"); @@ -357,11 +357,11 @@ getProcessorsDistribution (void) IF_DEBUG(scheduler, debugBelch("[*] Number of active processors in group %u detected: %u\n", i, cpuGroupDistCache[i])); } } -#endif } return cpuGroupDistCache; } +#endif static uint32_t* getProcessorsCumulativeSum(void) @@ -376,10 +376,10 @@ getProcessorsCumulativeSum(void) uint8_t n_groups = getNumberOfProcessorsGroups(); cpuGroupCumulativeCache = malloc(n_groups * sizeof(uint32_t)); memset(cpuGroupCumulativeCache, 0, n_groups * sizeof(uint32_t)); - uint8_t* proc_dist = getProcessorsDistribution(); - uint32_t cum_num_proc = 0; #if x86_64_HOST_ARCH + uint8_t* proc_dist = getProcessorsDistribution(); + uint32_t cum_num_proc = 0; for (int i = 0; i < n_groups; i++) { cpuGroupCumulativeCache[i] = cum_num_proc; @@ -593,11 +593,11 @@ void releaseThreadNode (void) { if (osNumaAvailable()) { - StgWord processMask; - StgWord systemMask; + PDWORD_PTR processMask = NULL; + PDWORD_PTR systemMask = NULL; if (!GetProcessAffinityMask(GetCurrentProcess(), - &processMask, - &systemMask)) + processMask, + systemMask)) { sysErrorBelch( "releaseThreadNode: Error resetting affinity of thread: %lu", @@ -605,7 +605,7 @@ void releaseThreadNode (void) stg_exit(EXIT_FAILURE); } - if (!SetThreadAffinityMask(GetCurrentThread(), processMask)) + if (!SetThreadAffinityMask(GetCurrentThread(), *processMask)) { sysErrorBelch( "releaseThreadNode: Error reseting NUMA affinity mask of thread: %lu.", diff --git a/testsuite/timeout/WinCBindings.hsc b/testsuite/timeout/WinCBindings.hsc index 87e4341..d9c08ee 100644 --- a/testsuite/timeout/WinCBindings.hsc +++ b/testsuite/timeout/WinCBindings.hsc @@ -314,7 +314,7 @@ foreign import WINDOWS_CCONV unsafe "windows.h CreateProcessW" -> BOOL -> DWORD -> LPVOID -> LPCTSTR -> LPSTARTUPINFO -> LPPROCESS_INFORMATION -> IO BOOL -foreign import WINDOWS_CCONV unsafe "string.h" memset :: Ptr a -> CInt -> CSize -> IO (Ptr a) +foreign import ccall unsafe "string.h" memset :: Ptr a -> CInt -> CSize -> IO (Ptr a) foreign import WINDOWS_CCONV unsafe "windows.h SetInformationJobObject" setInformationJobObject :: HANDLE -> JOBOBJECTINFOCLASS -> LPVOID -> DWORD -> IO BOOL @@ -328,6 +328,7 @@ foreign import WINDOWS_CCONV unsafe "windows.h GetQueuedCompletionStatus" setJobParameters :: HANDLE -> IO BOOL setJobParameters hJob = alloca $ \p_jeli -> do let jeliSize = sizeOf (undefined :: JOBOBJECT_EXTENDED_LIMIT_INFORMATION) + _ <- memset p_jeli 0 $ fromIntegral jeliSize -- Configure all child processes associated with the job to terminate when the -- Last process in the job terminates. This prevent half dead processes and that From git at git.haskell.org Tue Dec 6 14:07:17 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Dec 2016 14:07:17 +0000 (UTC) Subject: [commit: ghc] master: Give concrete example for #12784 in 8.0.2 release notes (eec02ab) Message-ID: <20161206140717.80FE53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eec02ab7c8433465cc8d6be0a8889e7c6a222fb0/ghc >--------------------------------------------------------------- commit eec02ab7c8433465cc8d6be0a8889e7c6a222fb0 Author: Ryan Scott Date: Tue Dec 6 09:03:41 2016 -0500 Give concrete example for #12784 in 8.0.2 release notes Summary: We mentioned that there were "some programs" that failed to typecheck due to #12784, but given how surprisingly common this issue has been, it'd be prudent to at least give one example of the bug in the release notes. Reviewers: simonpj, bgamari, austin, rwbarton Reviewed By: rwbarton Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2786 GHC Trac Issues: #12784 >--------------------------------------------------------------- eec02ab7c8433465cc8d6be0a8889e7c6a222fb0 docs/users_guide/8.0.2-notes.rst | 21 +++++++++++++++++++-- 1 file changed, 19 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/8.0.2-notes.rst b/docs/users_guide/8.0.2-notes.rst index fa7aa8d..237c3b9 100644 --- a/docs/users_guide/8.0.2-notes.rst +++ b/docs/users_guide/8.0.2-notes.rst @@ -68,8 +68,25 @@ Language foo :: m () - Some programs using :ghc-flag:`-XDefaultSignatures` that incorrectly - type-checked in GHC 8.0.1 are now rejected by GHC 8.0.2. See - :ghc-ticket:`12784` for details. + type-checked in GHC 8.0.1 are now rejected by GHC 8.0.2. Here is a + characteristic example: :: + + class Monad m => MonadSupply m where + fresh :: m Integer + default fresh :: (MonadTrans t, MonadSupply m) => t m Integer + fresh = lift fresh + + instance MonadSupply m => MonadSupply (IdentityT m) + + Note that the ``m`` in the default type signature is being used in + a completely different way than the ``m`` in the non-default signature! + We can fix this (in a backwards-compatible way) like so: :: + + class Monad m => MonadSupply m where + fresh :: m Integer + default fresh :: (MonadTrans t, MonadSupply m', m ~ t m') => m Integer + -- Same 'm Integer' after the '=>' + fresh = lift fresh - Some programs which combine default type class method implementations and overlapping instances may now fail to type-check. Here is an example: :: From git at git.haskell.org Tue Dec 6 20:06:39 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Dec 2016 20:06:39 +0000 (UTC) Subject: [commit: ghc] master: Overhaul GC stats (24e6594) Message-ID: <20161206200639.49F553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/24e6594cc7890babe69b8ba122d171affabad2d1/ghc >--------------------------------------------------------------- commit 24e6594cc7890babe69b8ba122d171affabad2d1 Author: Simon Marlow Date: Fri Nov 25 16:45:43 2016 +0000 Overhaul GC stats Summary: Visible API changes: * The C struct `GCDetails` gives the stats about a single GC. This is passed to the `gcDone()` callback if one is set via the RtsConfig. (previously we just passed a collection of values, so this is more extensible, at the expense of breaking the existing API) * `RTSStats` gives cumulative stats since the start of the program, and includes the `GCDetails` for the most recent GC. This struct can be obtained via `getRTSStats()` (the old `getGCStats()` has been removed, and `getGCStatsEnabled()` has been renamed to `getRTSStatsEnabled()`) Improvements: * The per-GC stats and cumulative stats are now cleanly separated. * Inside the RTS we have a top-level `RTSStats` struct to keep all our stats in, previously this was just a collection of strangely-named variables. This struct is mostly just copied in `getRTSStats()`, so the implementation of that function is a lot shorter. * Types are more consistent. We use a uint64_t byte count for all memory values, and Time for all time values. * Names are more consistent. We use a suffix `_bytes` for all byte counts and `_ns` for all time values. * We now collect information about the amount of memory in large objects and compact objects in `GCDetails`. (the latter was the reason I started doing this patch but it seems to have ballooned a bit!) * I fixed a bug in the calculation of the elapsed MUT time, and added an ASSERT to stop the calculations going wrong in the future. For now I kept the Haskell API in `GHC.Stats` the same, by impedence-matching with the new API. We could either break that API and make it match the C API more closely, or we could add a new API and deprecate the old one. Opinions welcome. This stuff is very easy to get wrong, and it's hard to test. Reviews welcome! Test Plan: manual testing validate Reviewers: bgamari, niteria, austin, ezyang, hvr, erikd, rwbarton, Phyx Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2756 >--------------------------------------------------------------- 24e6594cc7890babe69b8ba122d171affabad2d1 includes/Rts.h | 33 +--- includes/RtsAPI.h | 115 +++++++++++- includes/rts/Time.h | 43 +++++ includes/rts/storage/GC.h | 55 ------ libraries/base/GHC/Stats.hsc | 260 +++++++++++++++++++------ rts/RtsSymbols.c | 4 +- rts/Stats.c | 437 +++++++++++++++++++++---------------------- rts/Stats.h | 2 +- rts/sm/GC.c | 7 +- rts/sm/Storage.c | 22 +++ rts/sm/Storage.h | 4 +- 11 files changed, 598 insertions(+), 384 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 24e6594cc7890babe69b8ba122d171affabad2d1 From git at git.haskell.org Tue Dec 6 20:06:42 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Dec 2016 20:06:42 +0000 (UTC) Subject: [commit: ghc] master: Mark rn017 and T7672 as expect_broken(#12930) with -DDEBUG (19ae142) Message-ID: <20161206200642.1A00C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/19ae142364058e258122f4bb68ef4b9aa6e41890/ghc >--------------------------------------------------------------- commit 19ae142364058e258122f4bb68ef4b9aa6e41890 Author: Simon Marlow Date: Tue Dec 6 15:43:21 2016 +0000 Mark rn017 and T7672 as expect_broken(#12930) with -DDEBUG >--------------------------------------------------------------- 19ae142364058e258122f4bb68ef4b9aa6e41890 testsuite/tests/rename/should_compile/all.T | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/rename/should_compile/all.T b/testsuite/tests/rename/should_compile/all.T index 90d955b..531ff4f 100644 --- a/testsuite/tests/rename/should_compile/all.T +++ b/testsuite/tests/rename/should_compile/all.T @@ -26,6 +26,7 @@ test('rn012', test('rn013', normal, compile, ['']) test('rn017', [ + when(compiler_debugged(), expect_broken(12930)), extra_clean(['RnAux017.hi', 'RnAux017.o', 'RnAux017.hi-boot', 'RnAux017.o-boot'])], multimod_compile, @@ -212,7 +213,8 @@ test('T7167', normal, compile, ['']) test('T7336', expect_broken(7336), compile, ['-Wall']) test('T2435', normal, multimod_compile, ['T2435','-v0']) -test('T7672', normal, multimod_compile, ['T7672','-v0']) +test('T7672', when(compiler_debugged(), expect_broken(12930)), + multimod_compile, ['T7672','-v0']) test('T7963', [extra_clean(['T7963a.hi', 'T7963a.o', 'T7963.imports'])], From git at git.haskell.org Tue Dec 6 22:14:54 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Dec 2016 22:14:54 +0000 (UTC) Subject: [commit: ghc] master: Fix unsafe usage of `is_iloc` selector in Ord instance for ImportSpec (6e4188a) Message-ID: <20161206221454.B054A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6e4188abf36d3b489ff7c9586ca49fe922f2beb7/ghc >--------------------------------------------------------------- commit 6e4188abf36d3b489ff7c9586ca49fe922f2beb7 Author: Matthew Pickering Date: Tue Dec 6 18:09:55 2016 +0000 Fix unsafe usage of `is_iloc` selector in Ord instance for ImportSpec Summary: This fixes tests rn017, T7672 and closed #12930. Both these tests were self referential module imports through hs-boot files. As a result, I am quite suspicious of what the ImpAll constructor is used for. I had a brief hunt around but couldn't immediately see whether it was necessary. Reviewers: austin, bgamari Subscribers: simonpj, thomie, nomeata Differential Revision: https://phabricator.haskell.org/D2793 GHC Trac Issues: #12930 >--------------------------------------------------------------- 6e4188abf36d3b489ff7c9586ca49fe922f2beb7 compiler/basicTypes/RdrName.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/compiler/basicTypes/RdrName.hs b/compiler/basicTypes/RdrName.hs index d60522f..c4e3228 100644 --- a/compiler/basicTypes/RdrName.hs +++ b/compiler/basicTypes/RdrName.hs @@ -1137,7 +1137,12 @@ instance Eq ImpItemSpec where p1 == p2 = case p1 `compare` p2 of EQ -> True; _ -> False instance Ord ImpItemSpec where - compare is1 is2 = is_iloc is1 `compare` is_iloc is2 + compare is1 is2 = + case (is1, is2) of + (ImpAll, ImpAll) -> EQ + (ImpAll, _) -> GT + (_, ImpAll) -> LT + (ImpSome _ l1, ImpSome _ l2) -> l1 `compare` l2 bestImport :: [ImportSpec] -> ImportSpec From git at git.haskell.org Tue Dec 6 22:14:57 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Dec 2016 22:14:57 +0000 (UTC) Subject: [commit: ghc] master: Revert "Mark rn017 and T7672 as expect_broken(#12930) with -DDEBUG" (eafa06d) Message-ID: <20161206221457.67C013A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eafa06dce4aa815159ebba5a34d5137cf401ffbc/ghc >--------------------------------------------------------------- commit eafa06dce4aa815159ebba5a34d5137cf401ffbc Author: Matthew Pickering Date: Tue Dec 6 22:14:41 2016 +0000 Revert "Mark rn017 and T7672 as expect_broken(#12930) with -DDEBUG" This reverts commit 19ae142364058e258122f4bb68ef4b9aa6e41890. >--------------------------------------------------------------- eafa06dce4aa815159ebba5a34d5137cf401ffbc testsuite/tests/rename/should_compile/all.T | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/testsuite/tests/rename/should_compile/all.T b/testsuite/tests/rename/should_compile/all.T index 531ff4f..90d955b 100644 --- a/testsuite/tests/rename/should_compile/all.T +++ b/testsuite/tests/rename/should_compile/all.T @@ -26,7 +26,6 @@ test('rn012', test('rn013', normal, compile, ['']) test('rn017', [ - when(compiler_debugged(), expect_broken(12930)), extra_clean(['RnAux017.hi', 'RnAux017.o', 'RnAux017.hi-boot', 'RnAux017.o-boot'])], multimod_compile, @@ -213,8 +212,7 @@ test('T7167', normal, compile, ['']) test('T7336', expect_broken(7336), compile, ['-Wall']) test('T2435', normal, multimod_compile, ['T2435','-v0']) -test('T7672', when(compiler_debugged(), expect_broken(12930)), - multimod_compile, ['T7672','-v0']) +test('T7672', normal, multimod_compile, ['T7672','-v0']) test('T7963', [extra_clean(['T7963a.hi', 'T7963a.o', 'T7963.imports'])], From git at git.haskell.org Tue Dec 6 22:23:03 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Dec 2016 22:23:03 +0000 (UTC) Subject: [commit: packages/hpc] master: Bump directory upper bound to <1.4 (8625c1c) Message-ID: <20161206222303.82A193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : master Link : http://git.haskell.org/packages/hpc.git/commitdiff/8625c1c0550719437acad89d49401cf048990084 >--------------------------------------------------------------- commit 8625c1c0550719437acad89d49401cf048990084 Author: Ben Gamari Date: Tue Dec 6 17:21:24 2016 -0500 Bump directory upper bound to <1.4 >--------------------------------------------------------------- 8625c1c0550719437acad89d49401cf048990084 hpc.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hpc.cabal b/hpc.cabal index 6ae6aa9..994ca28 100644 --- a/hpc.cabal +++ b/hpc.cabal @@ -37,7 +37,7 @@ Library Build-Depends: base >= 4.4.1 && < 4.11, containers >= 0.4.1 && < 0.6, - directory >= 1.1 && < 1.3, + directory >= 1.1 && < 1.4, filepath >= 1 && < 1.5, time >= 1.2 && < 1.7 ghc-options: -Wall From git at git.haskell.org Tue Dec 6 23:01:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Dec 2016 23:01:26 +0000 (UTC) Subject: [commit: hsc2hs] master: Bump directory upper bound to < 1.4 (db6b601) Message-ID: <20161206230126.A827E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hsc2hs On branch : master Link : http://git.haskell.org/hsc2hs.git/commitdiff/db6b601bc8b59d5b58350f5585a3a7cd1715d887 >--------------------------------------------------------------- commit db6b601bc8b59d5b58350f5585a3a7cd1715d887 Author: Ben Gamari Date: Tue Dec 6 17:46:03 2016 -0500 Bump directory upper bound to < 1.4 >--------------------------------------------------------------- db6b601bc8b59d5b58350f5585a3a7cd1715d887 hsc2hs.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hsc2hs.cabal b/hsc2hs.cabal index 67378eb..9a53a8b 100644 --- a/hsc2hs.cabal +++ b/hsc2hs.cabal @@ -41,7 +41,7 @@ Executable hsc2hs Build-Depends: base >= 4 && < 5, containers >= 0.2 && < 0.6, - directory >= 1 && < 1.3, + directory >= 1 && < 1.4, filepath >= 1 && < 1.5, process >= 1.1 && < 1.5 From git at git.haskell.org Tue Dec 6 23:01:28 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Dec 2016 23:01:28 +0000 (UTC) Subject: [commit: hsc2hs] master: Add source repository stanza to cabal file (fbc552f) Message-ID: <20161206230128.AC5E23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hsc2hs On branch : master Link : http://git.haskell.org/hsc2hs.git/commitdiff/fbc552f4bb003edbdd52305a5eb34a903c9fe625 >--------------------------------------------------------------- commit fbc552f4bb003edbdd52305a5eb34a903c9fe625 Author: Ben Gamari Date: Tue Dec 6 18:01:05 2016 -0500 Add source repository stanza to cabal file >--------------------------------------------------------------- fbc552f4bb003edbdd52305a5eb34a903c9fe625 hsc2hs.cabal | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/hsc2hs.cabal b/hsc2hs.cabal index 9a53a8b..e76559b 100644 --- a/hsc2hs.cabal +++ b/hsc2hs.cabal @@ -25,6 +25,10 @@ build-type: Simple cabal-version: >=1.10 extra-source-files: changelog.md +source-repository head + Type: git + Location: git://git.haskell.org/hsc2hs + Executable hsc2hs Default-Language: Haskell2010 Main-Is: Main.hs From git at git.haskell.org Wed Dec 7 00:22:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Dec 2016 00:22:26 +0000 (UTC) Subject: [commit: ghc] master: Reduce the size of string literals in binaries. (b7e88ee) Message-ID: <20161207002226.DD2E43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b7e88ee0d87f41cf1d8aba62aa44d5bf0a7404ad/ghc >--------------------------------------------------------------- commit b7e88ee0d87f41cf1d8aba62aa44d5bf0a7404ad Author: Thijs Alkemade Date: Tue Dec 6 17:12:17 2016 -0500 Reduce the size of string literals in binaries. Removed the alignment for strings and mark then as cstring sections in the generated asm so the linker can merge duplicate sections. Reviewers: rwbarton, trofi, austin, trommler, simonmar, hvr, bgamari Reviewed By: hvr, bgamari Subscribers: simonpj, hvr, thomie Differential Revision: https://phabricator.haskell.org/D1290 GHC Trac Issues: #9577 >--------------------------------------------------------------- b7e88ee0d87f41cf1d8aba62aa44d5bf0a7404ad compiler/cmm/CLabel.hs | 8 +++++-- compiler/cmm/Cmm.hs | 1 + compiler/cmm/CmmUtils.hs | 7 ++++-- compiler/cmm/PprCmmDecl.hs | 1 + compiler/llvmGen/LlvmCodeGen/Data.hs | 2 ++ compiler/nativeGen/PPC/Ppr.hs | 6 +++++ compiler/nativeGen/PprBase.hs | 3 +++ compiler/nativeGen/SPARC/Ppr.hs | 3 +++ compiler/nativeGen/X86/Ppr.hs | 26 +++++++++++++++++----- testsuite/tests/codeGen/should_run/T9577.hs | 7 ++++++ .../tests/codeGen/should_run/T9577.stdout | 0 testsuite/tests/codeGen/should_run/T9577_A.hs | 8 +++++++ testsuite/tests/codeGen/should_run/all.T | 1 + 13 files changed, 64 insertions(+), 9 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b7e88ee0d87f41cf1d8aba62aa44d5bf0a7404ad From git at git.haskell.org Wed Dec 7 00:22:30 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Dec 2016 00:22:30 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #12919 (41ec722d) Message-ID: <20161207002230.2118E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/41ec722d71db0eadeddd582a23aab7347349185f/ghc >--------------------------------------------------------------- commit 41ec722d71db0eadeddd582a23aab7347349185f Author: Vladislav Zavialov Date: Tue Dec 6 18:48:27 2016 -0500 Test Trac #12919 Test Plan: make test TEST=T12919 Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2788 GHC Trac Issues: #12919 >--------------------------------------------------------------- 41ec722d71db0eadeddd582a23aab7347349185f testsuite/tests/typecheck/should_compile/T12919.hs | 22 ++++++++++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 23 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T12919.hs b/testsuite/tests/typecheck/should_compile/T12919.hs new file mode 100644 index 0000000..1f77c1c --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T12919.hs @@ -0,0 +1,22 @@ +{-# LANGUAGE TypeInType, TypeFamilies, GADTs, ConstraintKinds #-} + +module T12919 where + +import Data.Kind + +data N = Z + +data V :: N -> Type where + VZ :: V Z + +type family VC (n :: N) :: Type where + VC Z = Type + +type family VF (xs :: V n) (f :: VC n) :: Type where + VF VZ f = f + +data Dict c where + Dict :: c => Dict c + +prop :: xs ~ VZ => Dict (VF xs f ~ f) +prop = Dict diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index e2d65bd..088c6fa 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -556,3 +556,4 @@ test('T12734a', normal, compile_fail, ['']) test('T12763', normal, compile, ['']) test('T12797', normal, compile, ['']) test('T12925', normal, compile, ['']) +test('T12919', expect_broken(12919), compile, ['']) From git at git.haskell.org Wed Dec 7 03:11:37 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Dec 2016 03:11:37 +0000 (UTC) Subject: [commit: ghc] master: Mark T9577 as broken on Darwin due to #12937 (39143a4) Message-ID: <20161207031137.88BA63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/39143a474b5a983421eca9651e77f9c6e09b3958/ghc >--------------------------------------------------------------- commit 39143a474b5a983421eca9651e77f9c6e09b3958 Author: Ben Gamari Date: Tue Dec 6 22:10:47 2016 -0500 Mark T9577 as broken on Darwin due to #12937 >--------------------------------------------------------------- 39143a474b5a983421eca9651e77f9c6e09b3958 testsuite/tests/codeGen/should_run/all.T | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index fb7bdc2..7442caa 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -148,4 +148,6 @@ test('T12059', normal, compile_and_run, ['']) test('T12433', normal, compile_and_run, ['']) test('T12757', normal, compile_and_run, ['']) test('T12855', normal, compile_and_run, ['']) -test('T9577', [ unless(arch('x86_64') or arch('i386'),skip), only_ways(['normal']) ], compile_and_run, ['']) +test('T9577', [ unless(arch('x86_64') or arch('i386'),skip), + expect_broken(12937), + only_ways(['normal']) ], compile_and_run, ['']) From git at git.haskell.org Wed Dec 7 03:13:50 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Dec 2016 03:13:50 +0000 (UTC) Subject: [commit: ghc] master: Really mark T9577 as broken (4dd6b37) Message-ID: <20161207031350.F19A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4dd6b37fd540ad0243057f4aa29a93590d98de88/ghc >--------------------------------------------------------------- commit 4dd6b37fd540ad0243057f4aa29a93590d98de88 Author: Ben Gamari Date: Tue Dec 6 22:13:20 2016 -0500 Really mark T9577 as broken I failed at the last attempt. >--------------------------------------------------------------- 4dd6b37fd540ad0243057f4aa29a93590d98de88 testsuite/tests/codeGen/should_run/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 7442caa..cd212c3 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -149,5 +149,5 @@ test('T12433', normal, compile_and_run, ['']) test('T12757', normal, compile_and_run, ['']) test('T12855', normal, compile_and_run, ['']) test('T9577', [ unless(arch('x86_64') or arch('i386'),skip), - expect_broken(12937), + when(opsys('darwin'), expect_broken(12937)), only_ways(['normal']) ], compile_and_run, ['']) From git at git.haskell.org Wed Dec 7 10:59:49 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Dec 2016 10:59:49 +0000 (UTC) Subject: [commit: ghc] master: Overhaul of Compact Regions (#12455) (7036fde) Message-ID: <20161207105949.182DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7036fde9df61b6eae9719c7f6c656778c756bec9/ghc >--------------------------------------------------------------- commit 7036fde9df61b6eae9719c7f6c656778c756bec9 Author: Simon Marlow Date: Fri Jul 29 14:11:03 2016 +0100 Overhaul of Compact Regions (#12455) Summary: This commit makes various improvements and addresses some issues with Compact Regions (aka Compact Normal Forms). This was the most important thing I wanted to fix. Compaction previously prevented GC from running until it was complete, which would be a problem in a multicore setting. Now, we compact using a hand-written Cmm routine that can be interrupted at any point. When a GC is triggered during a sharing-enabled compaction, the GC has to traverse and update the hash table, so this hash table is now stored in the StgCompactNFData object. Previously, compaction consisted of a deepseq using the NFData class, followed by a traversal in C code to copy the data. This is now done in a single pass with hand-written Cmm (see rts/Compact.cmm). We no longer use the NFData instances, instead the Cmm routine evaluates components directly as it compacts. The new compaction is about 50% faster than the old one with no sharing, and a little faster on average with sharing (the cost of the hash table dominates when we're doing sharing). Static objects that don't (transitively) refer to any CAFs don't need to be copied into the compact region. In particular this means we often avoid copying Char values and small Int values, because these are static closures in the runtime. Each Compact# object can support a single compactAdd# operation at any given time, so the Data.Compact library now enforces mutual exclusion using an MVar stored in the Compact object. We now get exceptions rather than killing everything with a barf() when we encounter an object that cannot be compacted (a function, or a mutable object). We now also detect pinned objects, which can't be compacted either. The Data.Compact API has been refactored and cleaned up. A new compactSize operation returns the size (in bytes) of the compact object. Most of the documentation is in the Haddock docs for the compact library, which I've expanded and improved here. Various comments in the code have been improved, especially the main Note [Compact Normal Forms] in rts/sm/CNF.c. I've added a few tests, and expanded a few of the tests that were there. We now also run the tests with GHCi, and in a new test way that enables sanity checking (+RTS -DS). There's a benchmark in libraries/compact/tests/compact_bench.hs for measuring compaction speed and comparing sharing vs. no sharing. The field totalDataW in StgCompactNFData was unnecessary. Test Plan: * new unit tests * validate * tested manually that we can compact Data.Aeson data Reviewers: gcampax, bgamari, ezyang, austin, niteria, hvr, erikd Subscribers: thomie, simonpj Differential Revision: https://phabricator.haskell.org/D2751 GHC Trac Issues: #12455 >--------------------------------------------------------------- 7036fde9df61b6eae9719c7f6c656778c756bec9 compiler/prelude/primops.txt.pp | 36 +- docs/users_guide/sooner.rst | 7 + includes/rts/Flags.h | 1 + includes/rts/storage/ClosureMacros.h | 6 - includes/rts/storage/Closures.h | 86 +- includes/stg/MiscClosures.h | 6 +- libraries/base/Control/Exception.hs | 1 + libraries/base/Control/Exception/Base.hs | 1 + libraries/base/GHC/IO/Exception.hs | 31 + libraries/compact/Data/Compact.hs | 151 ++-- libraries/compact/Data/Compact/Internal.hs | 128 +-- libraries/compact/Data/Compact/Serialized.hs | 48 +- libraries/compact/tests/.gitignore | 3 - libraries/compact/tests/all.T | 25 +- libraries/compact/tests/compact_append.hs | 4 +- libraries/compact/tests/compact_autoexpand.hs | 3 +- libraries/compact/tests/compact_bench.hs | 28 + libraries/compact/tests/compact_bytestring.hs | 8 + libraries/compact/tests/compact_cycle.hs | 10 + libraries/compact/tests/compact_cycle.stdout | 2 + libraries/compact/tests/compact_function.hs | 10 + libraries/compact/tests/compact_function.stderr | 1 + libraries/compact/tests/compact_gc.hs | 12 + libraries/compact/tests/compact_gc.stdout | 13 + ...mpact_simple_array.hs => compact_huge_array.hs} | 9 +- libraries/compact/tests/compact_largemap.hs | 10 + libraries/compact/tests/compact_largemap.stdout | 2 + libraries/compact/tests/compact_loop.hs | 3 +- libraries/compact/tests/compact_mutable.hs | 13 + libraries/compact/tests/compact_mutable.stderr | 1 + libraries/compact/tests/compact_pinned.hs | 6 + libraries/compact/tests/compact_pinned.stderr | 1 + libraries/compact/tests/compact_serialize.hs | 3 +- libraries/compact/tests/compact_share.hs | 14 + libraries/compact/tests/compact_share.stdout | 4 + libraries/compact/tests/compact_simple.hs | 8 +- libraries/compact/tests/compact_simple.stdout | 2 + libraries/compact/tests/compact_simple_array.hs | 7 +- libraries/compact/tests/compact_threads.hs | 21 + libraries/compact/tests/compact_threads.stdout | 1 + rts/Compact.cmm | 437 +++++++++++ rts/Hash.c | 33 +- rts/Hash.h | 4 + rts/Prelude.h | 6 + rts/PrimOps.cmm | 131 --- rts/Printer.c | 2 +- rts/RtsFlags.c | 5 + rts/RtsStartup.c | 3 + rts/RtsSymbols.c | 4 +- rts/Stats.c | 22 +- rts/StgMiscClosures.cmm | 15 +- rts/Trace.h | 1 + rts/package.conf.in | 6 + rts/sm/CNF.c | 874 +++++++++------------ rts/sm/CNF.h | 22 +- rts/sm/Evac.c | 32 +- rts/sm/Sanity.c | 4 +- rts/sm/Scav.c | 64 +- rts/sm/ShouldCompact.h | 26 + rts/sm/Storage.c | 2 + rts/win32/libHSbase.def | 3 + testsuite/config/ghc | 3 + utils/deriveConstants/Main.hs | 4 + 63 files changed, 1515 insertions(+), 914 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7036fde9df61b6eae9719c7f6c656778c756bec9 From git at git.haskell.org Wed Dec 7 14:15:42 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Dec 2016 14:15:42 +0000 (UTC) Subject: [commit: ghc] master: Ignore output for compact_gc: sizes change when profiling (c02aeb5) Message-ID: <20161207141542.D70AF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c02aeb5cf73669796e262a481b6dc933ee88c390/ghc >--------------------------------------------------------------- commit c02aeb5cf73669796e262a481b6dc933ee88c390 Author: Simon Marlow Date: Wed Dec 7 13:18:39 2016 +0000 Ignore output for compact_gc: sizes change when profiling >--------------------------------------------------------------- c02aeb5cf73669796e262a481b6dc933ee88c390 libraries/compact/tests/all.T | 2 +- libraries/compact/tests/compact_gc.stdout | 13 ------------- 2 files changed, 1 insertion(+), 14 deletions(-) diff --git a/libraries/compact/tests/all.T b/libraries/compact/tests/all.T index bdcf522..753592e 100644 --- a/libraries/compact/tests/all.T +++ b/libraries/compact/tests/all.T @@ -13,7 +13,7 @@ test('compact_cycle', extra_run_opts('+RTS -K1m'), compile_and_run, ['']) test('compact_function', exit_code(1), compile_and_run, ['']) test('compact_mutable', exit_code(1), compile_and_run, ['']) test('compact_pinned', exit_code(1), compile_and_run, ['']) -test('compact_gc', normal, compile_and_run, ['']) +test('compact_gc', ignore_stdout, compile_and_run, ['']) test('compact_share', normal, compile_and_run, ['']) test('compact_bench', [ ignore_stdout, extra_run_opts('100') ], compile_and_run, ['']) diff --git a/libraries/compact/tests/compact_gc.stdout b/libraries/compact/tests/compact_gc.stdout deleted file mode 100644 index c44d588..0000000 --- a/libraries/compact/tests/compact_gc.stdout +++ /dev/null @@ -1,13 +0,0 @@ -2228224 -2228224 -2228224 -2228224 -2228224 -2228224 -2228224 -2228224 -2228224 -2228224 -2228224 -137798 -2228224 From git at git.haskell.org Wed Dec 7 14:15:45 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Dec 2016 14:15:45 +0000 (UTC) Subject: [commit: ghc] master: Fix the test with -O (5aa9c75) Message-ID: <20161207141545.89BD93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5aa9c750c6c3adc47a8e526007254b1f49de1d16/ghc >--------------------------------------------------------------- commit 5aa9c750c6c3adc47a8e526007254b1f49de1d16 Author: Simon Marlow Date: Wed Dec 7 13:19:01 2016 +0000 Fix the test with -O Static string optimisation means we get a ForeignPtr with an IORef inside it, leading to a different error. >--------------------------------------------------------------- 5aa9c750c6c3adc47a8e526007254b1f49de1d16 libraries/compact/tests/compact_pinned.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/compact/tests/compact_pinned.hs b/libraries/compact/tests/compact_pinned.hs index a2a45bb..39dda61 100644 --- a/libraries/compact/tests/compact_pinned.hs +++ b/libraries/compact/tests/compact_pinned.hs @@ -3,4 +3,4 @@ import Control.Exception import qualified Data.ByteString.Char8 as B import Data.Compact -main = compact (B.pack "abc") +main = compact (B.pack ['a'..'c']) From git at git.haskell.org Wed Dec 7 14:15:48 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Dec 2016 14:15:48 +0000 (UTC) Subject: [commit: ghc] master: Fix crashes in hash table scanning with THREADED_RTS (9043a40) Message-ID: <20161207141548.3BE7F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9043a4002623679989a2fdc4e97d484a9d58d619/ghc >--------------------------------------------------------------- commit 9043a4002623679989a2fdc4e97d484a9d58d619 Author: Simon Marlow Date: Wed Dec 7 13:20:03 2016 +0000 Fix crashes in hash table scanning with THREADED_RTS See comments. >--------------------------------------------------------------- 9043a4002623679989a2fdc4e97d484a9d58d619 rts/sm/Scav.c | 22 +++++++++++++++++++--- 1 file changed, 19 insertions(+), 3 deletions(-) diff --git a/rts/sm/Scav.c b/rts/sm/Scav.c index 10ce1e4..bbe049c 100644 --- a/rts/sm/Scav.c +++ b/rts/sm/Scav.c @@ -105,13 +105,26 @@ scavengeTSO (StgTSO *tso) Scavenging compact objects ------------------------------------------------------------------------- */ +typedef struct { + // We must save gct when calling mapHashTable(), which is compiled + // without GCThread.h and so uses a different calling convention. + // See also GC.c:mark_root where we do a similar thing. + gc_thread *saved_gct; + HashTable *newHash; +} MapHashData; + static void -evacuate_hash_entry(HashTable *newHash, StgWord key, const void *value) +evacuate_hash_entry(MapHashData *dat, StgWord key, const void *value) { StgClosure *p = (StgClosure*)key; +#ifdef THREADED_RTS + gc_thread *old_gct = gct; +#endif + SET_GCT(dat->saved_gct); evacuate(&p); - insertHashTable(newHash, (StgWord)p, value); + insertHashTable(dat->newHash, (StgWord)p, value); + SET_GCT(old_gct); } static void @@ -122,8 +135,11 @@ scavenge_compact(StgCompactNFData *str) gct->eager_promotion = false; if (str->hash) { + MapHashData dat; + dat.saved_gct = gct; HashTable *newHash = allocHashTable(); - mapHashTable(str->hash, (void*)newHash, (MapHashFn)evacuate_hash_entry); + dat.newHash = newHash; + mapHashTable(str->hash, (void*)&dat, (MapHashFn)evacuate_hash_entry); freeHashTable(str->hash, NULL); str->hash = newHash; } From git at git.haskell.org Wed Dec 7 15:50:25 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Dec 2016 15:50:25 +0000 (UTC) Subject: [commit: ghc] master: rts: Use pthread itimer implementation on Darwin (d70d452) Message-ID: <20161207155025.3CE143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d70d452a38bed3321bfc3c14074a6b3e1f30a090/ghc >--------------------------------------------------------------- commit d70d452a38bed3321bfc3c14074a6b3e1f30a090 Author: Ben Gamari Date: Wed Dec 7 08:50:52 2016 -0500 rts: Use pthread itimer implementation on Darwin We want to avoid using SIGALRM whenever possible since we will interrupt long-running system calls. See #10840. Test Plan: Validate on Darwin Reviewers: austin, erikd, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2796 GHC Trac Issues: #10840 >--------------------------------------------------------------- d70d452a38bed3321bfc3c14074a6b3e1f30a090 rts/posix/Itimer.c | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/rts/posix/Itimer.c b/rts/posix/Itimer.c index ee93dd7..59d34be 100644 --- a/rts/posix/Itimer.c +++ b/rts/posix/Itimer.c @@ -30,6 +30,15 @@ #endif /* + * We want to avoid using the SIGALRM signals whenever possible as these signals + * interrupt system calls (see #10840) and can be overridden by user code. On + * Darwin we can use a dedicated thread and usleep. + */ +#if defined(darwin_HOST_OS) +#define USE_PTHREAD_FOR_ITIMER +#endif + +/* * On Linux in the threaded RTS we can use timerfd_* (introduced in Linux * 2.6.25) and a thread instead of alarm signals. It avoids the risk of * interrupting syscalls (see #10840) and the risk of being accidentally From git at git.haskell.org Wed Dec 7 15:50:28 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Dec 2016 15:50:28 +0000 (UTC) Subject: [commit: ghc] master: Don't barf() on failures in loadArchive() (83d69dc) Message-ID: <20161207155028.0E5033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/83d69dca896c7df1f2a36268d5b45c9283985ebf/ghc >--------------------------------------------------------------- commit 83d69dca896c7df1f2a36268d5b45c9283985ebf Author: Ben Gamari Date: Wed Dec 7 08:51:02 2016 -0500 Don't barf() on failures in loadArchive() This patch replaces calls to barf() in loadArchive() with proper error handling. Test Plan: GHC CI Reviewers: rwbarton, erikd, hvr, austin, simonmar, bgamari Reviewed By: bgamari Subscribers: thomie Tags: #ghc Differential Revision: https://phabricator.haskell.org/D2652 GHC Trac Issues: #12388 >--------------------------------------------------------------- 83d69dca896c7df1f2a36268d5b45c9283985ebf includes/Rts.h | 6 +- rts/LinkerInternals.h | 7 +- rts/linker/LoadArchive.c | 471 +++++++++++++++++++++++++++++------------------ 3 files changed, 291 insertions(+), 193 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 83d69dca896c7df1f2a36268d5b45c9283985ebf From git at git.haskell.org Wed Dec 7 19:31:30 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Dec 2016 19:31:30 +0000 (UTC) Subject: [commit: ghc] master: Add HsSyn prettyprinter tests (499e438) Message-ID: <20161207193130.EE7D83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/499e43824bda967546ebf95ee33ec1f84a114a7c/ghc >--------------------------------------------------------------- commit 499e43824bda967546ebf95ee33ec1f84a114a7c Author: Alan Zimmerman Date: Tue Nov 8 21:37:48 2016 +0200 Add HsSyn prettyprinter tests Summary: Add prettyprinter tests, which take a file, parse it, pretty print it, re-parse the pretty printed version and then compare the original and new ASTs (ignoring locations) Updates haddock submodule to match the AST changes. There are three issues outstanding 1. Extra parens around a context are not reproduced. This will require an AST change and will be done in a separate patch. 2. Currently if an `HsTickPragma` is found, this is not pretty-printed, to prevent noise in the output. I am not sure what the desired behaviour in this case is, so have left it as before. Test Ppr047 is marked as expected fail for this. 3. Apart from in a context, the ParsedSource AST keeps all the parens from the original source. Something is happening in the renamer to remove the parens around visible type application, causing T12530 to fail, as the dumped splice decl is after the renamer. This needs to be fixed by keeping the parens, but I do not know where they are being removed. I have amended the test to pass, by removing the parens in the expected output. Test Plan: ./validate Reviewers: goldfire, mpickering, simonpj, bgamari, austin Reviewed By: simonpj, bgamari Subscribers: simonpj, goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2752 GHC Trac Issues: #3384 >--------------------------------------------------------------- 499e43824bda967546ebf95ee33ec1f84a114a7c compiler/basicTypes/BasicTypes.hs | 90 ++++- compiler/basicTypes/DataCon.hs | 2 +- compiler/basicTypes/MkId.hs | 3 +- compiler/basicTypes/Var.hs | 3 + compiler/coreSyn/PprCore.hs | 2 +- compiler/deSugar/Coverage.hs | 5 +- compiler/deSugar/DsArrows.hs | 2 +- compiler/deSugar/DsCCall.hs | 3 +- compiler/deSugar/DsForeign.hs | 2 +- compiler/deSugar/DsMeta.hs | 23 +- compiler/deSugar/MatchLit.hs | 6 +- compiler/hsSyn/Convert.hs | 126 +++--- compiler/hsSyn/HsBinds.hs | 75 ++-- compiler/hsSyn/HsDecls.hs | 212 ++++++---- compiler/hsSyn/HsExpr.hs | 252 +++++++----- compiler/hsSyn/HsExpr.hs-boot | 24 +- compiler/hsSyn/HsImpExp.hs | 25 +- compiler/hsSyn/HsLit.hs | 43 ++- compiler/hsSyn/HsPat.hs | 25 +- compiler/hsSyn/HsPat.hs-boot | 4 +- compiler/hsSyn/HsSyn.hs | 3 +- compiler/hsSyn/HsTypes.hs | 130 ++++--- compiler/hsSyn/HsUtils.hs | 43 ++- compiler/hsSyn/PlaceHolder.hs | 7 + compiler/iface/BuildTyCl.hs | 2 +- compiler/iface/LoadIface.hs | 3 +- compiler/iface/TcIface.hs | 2 +- compiler/main/HeaderInfo.hs | 2 +- compiler/parser/Lexer.x | 103 ++--- compiler/parser/Parser.y | 56 +-- compiler/parser/RdrHsSyn.hs | 30 +- compiler/prelude/ForeignCall.hs | 12 +- compiler/prelude/PrimOp.hs | 3 +- compiler/prelude/TysWiredIn.hs | 30 +- compiler/rename/RnEnv.hs | 9 +- compiler/rename/RnExpr.hs | 8 +- compiler/rename/RnPat.hs | 2 +- compiler/rename/RnSplice.hs | 16 +- compiler/rename/RnTypes.hs | 26 +- compiler/stranal/WorkWrap.hs | 6 +- compiler/typecheck/Inst.hs | 7 +- compiler/typecheck/TcAnnotations.hs | 2 +- compiler/typecheck/TcArrows.hs | 4 +- compiler/typecheck/TcBinds.hs | 2 +- compiler/typecheck/TcEnv.hs | 5 +- compiler/typecheck/TcGenDeriv.hs | 22 +- compiler/typecheck/TcGenFunctor.hs | 5 +- compiler/typecheck/TcGenGenerics.hs | 12 +- compiler/typecheck/TcHsSyn.hs | 4 +- compiler/typecheck/TcHsType.hs | 4 +- compiler/typecheck/TcInstDcls.hs | 2 +- compiler/typecheck/TcPat.hs | 3 +- compiler/typecheck/TcPatSyn.hs | 9 +- compiler/typecheck/TcSplice.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 2 +- compiler/typecheck/TcTyDecls.hs | 2 +- compiler/typecheck/TcTypeable.hs | 6 +- compiler/utils/Binary.hs | 15 + compiler/utils/BooleanFormula.hs | 16 +- compiler/utils/Outputable.hs | 4 +- compiler/vectorise/Vectorise/Generic/PData.hs | 5 +- ghc.mk | 3 + testsuite/mk/boilerplate.mk | 1 + testsuite/tests/ado/ado002.stderr | 66 ++-- testsuite/tests/ado/ado003.stderr | 6 +- testsuite/tests/ado/ado005.stderr | 12 +- .../tests/arrows/should_fail/arrowfail004.stderr | 4 +- testsuite/tests/boxy/Base1.stderr | 4 +- .../dependent/should_fail/PromotedClass.stderr | 5 +- .../tests/dependent/should_fail/RAE_T32a.stderr | 2 +- .../tests/dependent/should_fail/T11334b.stderr | 18 +- testsuite/tests/ffi/should_fail/T10461.stderr | 2 +- testsuite/tests/ffi/should_fail/T3066.stderr | 3 +- testsuite/tests/ffi/should_fail/T7506.stderr | 2 +- .../ffi/should_fail/capi_value_function.stderr | 3 +- testsuite/tests/ffi/should_fail/ccfail001.stderr | 3 +- testsuite/tests/ffi/should_fail/ccfail002.stderr | 2 +- testsuite/tests/ffi/should_fail/ccfail004.stderr | 10 +- testsuite/tests/ffi/should_fail/ccfail005.stderr | 6 +- testsuite/tests/generics/GenDerivOutput.stderr | 56 +-- testsuite/tests/generics/GenDerivOutput1_0.stderr | 14 +- testsuite/tests/generics/GenDerivOutput1_1.stderr | 115 +++--- .../tests/generics/T10604/T10604_deriving.stderr | 68 ++-- .../ghc-api/annotations-literals/literals.stdout | 16 +- .../tests/ghc-api/annotations-literals/parsed.hs | 38 +- .../ghc-api/annotations-literals/parsed.stdout | 8 +- testsuite/tests/ghc-api/annotations/T10276.stderr | 24 +- testsuite/tests/ghc-api/annotations/T10313.stdout | 32 +- testsuite/tests/ghc-api/annotations/T11430.stdout | 2 +- testsuite/tests/ghc-api/annotations/t11430.hs | 14 +- testsuite/tests/ghci/scripts/T8959b.stderr | 4 +- .../haddock/haddock_examples/haddock.Test.stderr | 4 +- .../should_compile_flag_haddock/T11768.stderr | 2 +- .../should_compile_flag_haddock/haddockA028.stderr | 2 +- .../indexed-types/should_fail/SimpleFail14.stderr | 2 +- .../tests/indexed-types/should_fail/T12867.stderr | 4 +- .../tests/indexed-types/should_fail/T2664.stderr | 16 +- .../tests/indexed-types/should_fail/T2693.stderr | 6 +- .../tests/indexed-types/should_fail/T5439.stderr | 4 +- .../tests/indexed-types/should_fail/T7786.stderr | 12 +- testsuite/tests/monadfail/MonadFailErrors.stderr | 32 +- testsuite/tests/monadfail/MonadFailWarnings.stderr | 32 +- .../partial-sigs/should_compile/SplicesUsed.stderr | 8 +- .../partial-sigs/should_compile/T12845.stderr | 2 +- testsuite/tests/polykinds/PolyKinds04.stderr | 2 +- testsuite/tests/polykinds/PolyKinds07.stderr | 4 +- testsuite/tests/polykinds/T10503.stderr | 3 +- testsuite/tests/polykinds/T11399.stderr | 2 +- testsuite/tests/polykinds/T11520.stderr | 2 +- testsuite/tests/polykinds/T11611.stderr | 2 +- testsuite/tests/polykinds/T5716.stderr | 2 +- testsuite/tests/polykinds/T5716a.stderr | 2 +- testsuite/tests/polykinds/T6054.stderr | 6 +- testsuite/tests/polykinds/T7151.stderr | 2 +- testsuite/tests/polykinds/T7328.stderr | 2 +- testsuite/tests/polykinds/T7433.stderr | 2 +- testsuite/tests/polykinds/T7805.stderr | 2 +- testsuite/tests/printer/.gitignore | 17 + testsuite/tests/printer/Makefile | 195 ++++++++++ testsuite/tests/printer/Ppr001.hs | 7 + testsuite/tests/printer/Ppr002.hs | 46 +++ testsuite/tests/printer/Ppr003.hs | 11 + testsuite/tests/printer/Ppr004.hs | 81 ++++ testsuite/tests/printer/Ppr005.hs | 11 + testsuite/tests/printer/Ppr006.hs | 257 +++++++++++++ testsuite/tests/printer/Ppr006.stderr | 45 +++ testsuite/tests/printer/Ppr007.hs | 8 + testsuite/tests/printer/Ppr007.stderr | 17 + testsuite/tests/printer/Ppr008.hs | 213 ++++++++++ testsuite/tests/printer/Ppr009.hs | 9 + testsuite/tests/printer/Ppr009.stderr | 28 ++ testsuite/tests/printer/Ppr010.hs | 17 + testsuite/tests/printer/Ppr011.hs | 34 ++ testsuite/tests/printer/Ppr011.stderr | 12 + testsuite/tests/printer/Ppr012.hs | 42 ++ testsuite/tests/printer/Ppr012.stderr | 8 + testsuite/tests/printer/Ppr012.stdout | 186 +++++++++ testsuite/tests/printer/Ppr013.hs | 13 + testsuite/tests/printer/Ppr013.stderr | 6 + testsuite/tests/printer/Ppr014.hs | 59 +++ testsuite/tests/printer/Ppr014.stderr | 76 ++++ testsuite/tests/printer/Ppr015.hs | 5 + testsuite/tests/printer/Ppr016.hs | 4 + testsuite/tests/printer/Ppr016.stderr | 14 + testsuite/tests/printer/Ppr017.hs | 9 + testsuite/tests/printer/Ppr018.hs | 20 + testsuite/tests/printer/Ppr018.stderr | 12 + testsuite/tests/printer/Ppr019.hs | 427 +++++++++++++++++++++ testsuite/tests/printer/Ppr020.hs | 11 + testsuite/tests/printer/Ppr020.stderr | 31 ++ testsuite/tests/printer/Ppr021.hs | 63 +++ testsuite/tests/printer/Ppr021.stderr | 16 + testsuite/tests/printer/Ppr022.hs | 12 + testsuite/tests/printer/Ppr022.stderr | 28 ++ testsuite/tests/printer/Ppr023.hs | 37 ++ testsuite/tests/printer/Ppr023.stderr | 49 +++ testsuite/tests/printer/Ppr024.hs | 47 +++ testsuite/tests/printer/Ppr024.stderr | 6 + testsuite/tests/printer/Ppr025.hs | 30 ++ testsuite/tests/printer/Ppr025.stderr | 6 + testsuite/tests/printer/Ppr026.hs | 14 + testsuite/tests/printer/Ppr026.stderr | 6 + testsuite/tests/printer/Ppr027.hs | 5 + testsuite/tests/printer/Ppr028.hs | 12 + testsuite/tests/printer/Ppr028.stderr | 6 + testsuite/tests/printer/Ppr029.hs | 37 ++ testsuite/tests/printer/Ppr029.stderr | 16 + testsuite/tests/printer/Ppr030.hs | 10 + testsuite/tests/printer/Ppr030.stderr | 6 + testsuite/tests/printer/Ppr031.hs | 22 ++ testsuite/tests/printer/Ppr031.stderr | 46 +++ testsuite/tests/printer/Ppr032.hs | 40 ++ testsuite/tests/printer/Ppr032.stderr | 18 + testsuite/tests/printer/Ppr033.hs | 21 + testsuite/tests/printer/Ppr033.stderr | 8 + testsuite/tests/printer/Ppr034.hs | 423 ++++++++++++++++++++ testsuite/tests/printer/Ppr034.stderr | 42 ++ testsuite/tests/printer/Ppr035.hs | 14 + testsuite/tests/printer/Ppr036.hs | 15 + testsuite/tests/printer/Ppr036.stderr | 6 + testsuite/tests/printer/Ppr037.hs | 64 +++ testsuite/tests/printer/Ppr037.stderr | 48 +++ testsuite/tests/printer/Ppr038.hs | 26 ++ testsuite/tests/printer/Ppr039.hs | 30 ++ testsuite/tests/printer/Ppr039.stderr | 73 ++++ testsuite/tests/printer/Ppr040.hs | 43 +++ testsuite/tests/printer/Ppr040.stderr | 38 ++ .../should_run/T10104.hs => printer/Ppr041.hs} | 0 testsuite/tests/printer/Ppr042.hs | 8 + testsuite/tests/printer/Ppr042.stderr | 28 ++ .../tests/{th/T10620.hs => printer/Ppr043.hs} | 0 .../T1830_2.hs => printer/Ppr044.hs} | 0 testsuite/tests/printer/Ppr045.hs | 78 ++++ testsuite/tests/printer/Ppr046.hs | 36 ++ testsuite/tests/printer/Ppr046.stderr | 61 +++ testsuite/tests/printer/Ppr047.hs | 4 + testsuite/tests/printer/all.T | 47 +++ testsuite/tests/quasiquotation/T7918.hs | 2 +- testsuite/tests/rebindable/rebindable6.stderr | 36 +- .../tests/rename/should_fail/Misplaced.stderr | 2 +- .../tests/rename/should_fail/rnfail026.stderr | 2 +- testsuite/tests/roles/should_compile/T8958.stderr | 4 +- testsuite/tests/safeHaskell/ghci/p6.stderr | 2 +- .../safeHaskell/safeLanguage/SafeLang08.stderr | 2 +- .../safeHaskell/safeLanguage/SafeLang10.stderr | 6 +- .../safeHaskell/safeLanguage/SafeLang17.stderr | 6 +- .../tests/simplCore/should_compile/T7785.stderr | 2 +- .../tests/simplCore/should_compile/T8331.stderr | 2 +- .../tests/simplCore/should_compile/T8848a.stderr | 2 +- .../tests/simplCore/should_compile/simpl017.stderr | 18 +- testsuite/tests/th/T10598_TH.stderr | 74 ++-- testsuite/tests/th/T10638.stderr | 3 +- testsuite/tests/th/T12530.stderr | 2 +- testsuite/tests/th/T3177a.stderr | 6 +- testsuite/tests/th/T3319.stderr | 2 +- testsuite/tests/th/T3899a.hs | 3 +- testsuite/tests/th/T4436.stderr | 13 +- testsuite/tests/th/T5217.stderr | 6 +- testsuite/tests/th/T5358.stderr | 8 +- testsuite/tests/th/T5508.stderr | 8 +- testsuite/tests/th/T5700.stderr | 2 +- testsuite/tests/th/T5883.stderr | 2 +- testsuite/tests/th/T7532.stderr | 4 +- testsuite/tests/th/T8577.stderr | 4 +- testsuite/tests/th/T8761.stderr | 112 +++--- testsuite/tests/th/TH_PromotedTuple.stderr | 6 +- testsuite/tests/th/TH_exn2.stderr | 4 +- .../tests/th/TH_foreignCallingConventions.stderr | 33 +- testsuite/tests/th/TH_foreignInterruptible.stderr | 3 +- testsuite/tests/th/TH_pragma.stderr | 4 +- testsuite/tests/th/TH_unresolvedInfix2.stderr | 2 +- .../tests/typecheck/should_compile/T11339.stderr | 4 +- .../tests/typecheck/should_compile/tc211.stderr | 12 +- .../tests/typecheck/should_fail/T11464.stderr | 2 +- .../tests/typecheck/should_fail/T12124.stderr | 4 +- testsuite/tests/typecheck/should_fail/T2994.stderr | 2 +- testsuite/tests/typecheck/should_fail/T3540.stderr | 15 +- testsuite/tests/typecheck/should_fail/T3613.stderr | 8 +- .../tests/typecheck/should_fail/T7748a.stderr | 4 +- testsuite/tests/typecheck/should_fail/T7851.stderr | 8 +- testsuite/tests/typecheck/should_fail/T8603.stderr | 4 +- testsuite/tests/typecheck/should_fail/T9201.stderr | 2 +- testsuite/tests/typecheck/should_fail/T9612.stderr | 8 +- .../tests/typecheck/should_fail/tcfail028.stderr | 2 +- .../tests/typecheck/should_fail/tcfail070.stderr | 2 +- .../tests/typecheck/should_fail/tcfail103.stderr | 8 +- .../tests/typecheck/should_fail/tcfail128.stderr | 18 +- .../tests/typecheck/should_fail/tcfail132.stderr | 4 +- .../tests/typecheck/should_fail/tcfail146.stderr | 2 +- .../tests/typecheck/should_fail/tcfail162.stderr | 2 +- .../tests/typecheck/should_fail/tcfail165.stderr | 6 +- .../tests/typecheck/should_fail/tcfail168.stderr | 18 +- testsuite/tests/unboxedsums/ffi1.stderr | 7 +- .../wcompat-warnings/WCompatWarningsOn.stderr | 8 +- utils/check-ppr/Main.hs | 219 +++++++++++ utils/check-ppr/README | 20 + utils/check-ppr/check-ppr.cabal | 32 ++ utils/check-ppr/ghc.mk | 18 + utils/genprimopcode/Parser.y | 6 +- utils/genprimopcode/Syntax.hs | 8 +- utils/haddock | 2 +- 261 files changed, 5453 insertions(+), 1220 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 499e43824bda967546ebf95ee33ec1f84a114a7c From git at git.haskell.org Wed Dec 7 21:25:59 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Dec 2016 21:25:59 +0000 (UTC) Subject: [commit: ghc] master: Fix pretty printer test to nog generate stdout (58d78dc) Message-ID: <20161207212559.84CAA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/58d78dc0c522327858aa2fdce647a95c575ae7ee/ghc >--------------------------------------------------------------- commit 58d78dc0c522327858aa2fdce647a95c575ae7ee Author: Alan Zimmerman Date: Wed Dec 7 23:24:22 2016 +0200 Fix pretty printer test to nog generate stdout It was doing a dump to stdout, which is not repeatable across platforms. >--------------------------------------------------------------- 58d78dc0c522327858aa2fdce647a95c575ae7ee testsuite/tests/printer/Ppr012.hs | 2 - testsuite/tests/printer/Ppr012.stderr | 3 +- testsuite/tests/printer/Ppr012.stdout | 186 ---------------------------------- testsuite/tests/printer/all.T | 1 + 4 files changed, 3 insertions(+), 189 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 58d78dc0c522327858aa2fdce647a95c575ae7ee From git at git.haskell.org Wed Dec 7 21:38:55 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Dec 2016 21:38:55 +0000 (UTC) Subject: [commit: ghc] master: Remove stray commented out line in all.T (9bcc4e3) Message-ID: <20161207213855.3D3BF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9bcc4e335b34c00191e8897aa7393c3856e8996f/ghc >--------------------------------------------------------------- commit 9bcc4e335b34c00191e8897aa7393c3856e8996f Author: Alan Zimmerman Date: Wed Dec 7 23:36:23 2016 +0200 Remove stray commented out line in all.T >--------------------------------------------------------------- 9bcc4e335b34c00191e8897aa7393c3856e8996f testsuite/tests/printer/all.T | 1 - 1 file changed, 1 deletion(-) diff --git a/testsuite/tests/printer/all.T b/testsuite/tests/printer/all.T index 8a795f5..c39656e 100644 --- a/testsuite/tests/printer/all.T +++ b/testsuite/tests/printer/all.T @@ -9,7 +9,6 @@ test('Ppr008', normal, run_command, ['$MAKE -s --no-print-directory ppr008']) test('Ppr009', normal, run_command, ['$MAKE -s --no-print-directory ppr009']) test('Ppr010', normal, run_command, ['$MAKE -s --no-print-directory ppr010']) test('Ppr011', normal, run_command, ['$MAKE -s --no-print-directory ppr011']) -#test('Ppr012', ignore_stdout, run_command, ['$MAKE -s --no-print-directory ppr012']) test('Ppr012', normal, run_command, ['$MAKE -s --no-print-directory ppr012']) test('Ppr013', normal, run_command, ['$MAKE -s --no-print-directory ppr013']) test('Ppr014', normal, run_command, ['$MAKE -s --no-print-directory ppr014']) From git at git.haskell.org Thu Dec 8 09:21:29 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Dec 2016 09:21:29 +0000 (UTC) Subject: [commit: ghc] master: Ignore stderr of all printer tests (c5fbbac) Message-ID: <20161208092129.546633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c5fbbac9fdf86a94b636849e4aa6f1c4ecc9acf2/ghc >--------------------------------------------------------------- commit c5fbbac9fdf86a94b636849e4aa6f1c4ecc9acf2 Author: Alan Zimmerman Date: Thu Dec 8 10:50:37 2016 +0200 Ignore stderr of all printer tests >--------------------------------------------------------------- c5fbbac9fdf86a94b636849e4aa6f1c4ecc9acf2 testsuite/tests/printer/Ppr006.stderr | 45 ----------------- testsuite/tests/printer/Ppr007.stderr | 17 ------- testsuite/tests/printer/Ppr009.stderr | 28 ----------- testsuite/tests/printer/Ppr011.stderr | 12 ----- testsuite/tests/printer/Ppr012.stderr | 9 ---- testsuite/tests/printer/Ppr013.stderr | 6 --- testsuite/tests/printer/Ppr014.stderr | 76 ----------------------------- testsuite/tests/printer/Ppr016.stderr | 14 ------ testsuite/tests/printer/Ppr018.stderr | 12 ----- testsuite/tests/printer/Ppr020.stderr | 31 ------------ testsuite/tests/printer/Ppr021.stderr | 16 ------ testsuite/tests/printer/Ppr022.stderr | 28 ----------- testsuite/tests/printer/Ppr023.stderr | 49 ------------------- testsuite/tests/printer/Ppr024.stderr | 6 --- testsuite/tests/printer/Ppr025.stderr | 6 --- testsuite/tests/printer/Ppr026.stderr | 6 --- testsuite/tests/printer/Ppr028.stderr | 6 --- testsuite/tests/printer/Ppr029.stderr | 16 ------ testsuite/tests/printer/Ppr030.stderr | 6 --- testsuite/tests/printer/Ppr031.stderr | 46 ------------------ testsuite/tests/printer/Ppr032.stderr | 18 ------- testsuite/tests/printer/Ppr033.stderr | 8 --- testsuite/tests/printer/Ppr034.stderr | 42 ---------------- testsuite/tests/printer/Ppr036.stderr | 6 --- testsuite/tests/printer/Ppr037.stderr | 48 ------------------ testsuite/tests/printer/Ppr039.stderr | 73 --------------------------- testsuite/tests/printer/Ppr040.stderr | 38 --------------- testsuite/tests/printer/Ppr042.stderr | 28 ----------- testsuite/tests/printer/Ppr046.stderr | 61 ----------------------- testsuite/tests/printer/all.T | 92 +++++++++++++++++------------------ 30 files changed, 46 insertions(+), 803 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c5fbbac9fdf86a94b636849e4aa6f1c4ecc9acf2 From git at git.haskell.org Thu Dec 8 23:05:36 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Dec 2016 23:05:36 +0000 (UTC) Subject: [commit: ghc] master: Setup tcg_imports earlier during signature matching, so orphans are visible. (62332f3) Message-ID: <20161208230536.298663A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/62332f36b62431ddb9ab3c97365288c7d3fc2d39/ghc >--------------------------------------------------------------- commit 62332f36b62431ddb9ab3c97365288c7d3fc2d39 Author: Edward Z. Yang Date: Wed Dec 7 22:57:09 2016 -0800 Setup tcg_imports earlier during signature matching, so orphans are visible. Summary: Previously, we updated tcg_imports after doing all of the actual matching, which was fine for outputting the interface, but not good enough for checking if all type classes were implemented; we weren't treating orphans as visible (when they needed to be.) Fixes #12945. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2802 GHC Trac Issues: #12945 >--------------------------------------------------------------- 62332f36b62431ddb9ab3c97365288c7d3fc2d39 compiler/typecheck/TcBackpack.hs | 24 ++++++++++++++-------- testsuite/tests/backpack/should_compile/all.T | 1 + testsuite/tests/backpack/should_compile/bkp41.bkp | 18 ++++++++++++++++ .../tests/backpack/should_compile/bkp41.stderr | 13 ++++++++++++ 4 files changed, 47 insertions(+), 9 deletions(-) diff --git a/compiler/typecheck/TcBackpack.hs b/compiler/typecheck/TcBackpack.hs index 6f78499..7e7b30c 100644 --- a/compiler/typecheck/TcBackpack.hs +++ b/compiler/typecheck/TcBackpack.hs @@ -538,13 +538,24 @@ checkImplements impl_mod (IndefModule uid mod_name) = do let insts = indefUnitIdInsts uid -- STEP 1: Load the implementing interface, and make a RdrEnv - -- for its exports + -- for its exports. Also, add its 'ImportAvails' to 'tcg_imports', + -- so that we treat all orphan instances it provides as visible + -- when we verify that all instances are checked (see #12945), and so that + -- when we eventually write out the interface we record appropriate + -- dependency information. impl_iface <- initIfaceTcRn $ loadSysInterface (text "checkImplements 1") impl_mod let impl_gr = mkGlobalRdrEnv (gresFromAvails Nothing (mi_exports impl_iface)) nsubst = mkNameShape (moduleName impl_mod) (mi_exports impl_iface) + dflags <- getDynFlags + let avails = calculateAvails dflags + impl_iface False{- safe -} False{- boot -} + updGblEnv (\tcg_env -> tcg_env { + tcg_imports = tcg_imports tcg_env `plusImportAvails` avails + }) $ do + -- STEP 2: Load the *unrenamed, uninstantiated* interface for -- the ORIGINAL signature. We are going to eventually rename it, -- but we must proceed slowly, because it is NOT known if the @@ -579,15 +590,10 @@ checkImplements impl_mod (IndefModule uid mod_name) = do tcg_env <- getGblEnv checkHsigIface tcg_env impl_gr sig_details - -- STEP 7: Make sure we have the right exports and imports, - -- in case we're going to serialize this out (only relevant - -- if we're actually instantiating). - dflags <- getDynFlags - let avails = calculateAvails dflags - impl_iface False{- safe -} False{- boot -} + -- STEP 7: Return the updated 'TcGblEnv' with the signature exports, + -- so we write them out. return tcg_env { - tcg_exports = mi_exports sig_iface, - tcg_imports = tcg_imports tcg_env `plusImportAvails` avails + tcg_exports = mi_exports sig_iface } -- | Given 'tcg_mod', instantiate a 'ModIface' from the indefinite diff --git a/testsuite/tests/backpack/should_compile/all.T b/testsuite/tests/backpack/should_compile/all.T index 81bcb9a..1f0136f 100644 --- a/testsuite/tests/backpack/should_compile/all.T +++ b/testsuite/tests/backpack/should_compile/all.T @@ -32,3 +32,4 @@ test('bkp37', normal, backpack_compile, ['']) test('bkp38', normal, backpack_compile, ['']) test('bkp39', normal, backpack_compile, ['']) test('bkp40', normal, backpack_compile, ['']) +test('bkp41', normal, backpack_compile, ['']) diff --git a/testsuite/tests/backpack/should_compile/bkp41.bkp b/testsuite/tests/backpack/should_compile/bkp41.bkp new file mode 100644 index 0000000..e8b5b24 --- /dev/null +++ b/testsuite/tests/backpack/should_compile/bkp41.bkp @@ -0,0 +1,18 @@ +unit impl where + module A where + data T = T + module B(module A, module B) where + import A + instance Show T where + show T = "T" + +unit sig where + signature B where + data T = T + instance Show T + module App where + import B + app = print T + +unit main where + dependency sig[B=impl:B] diff --git a/testsuite/tests/backpack/should_compile/bkp41.stderr b/testsuite/tests/backpack/should_compile/bkp41.stderr new file mode 100644 index 0000000..0dfe754 --- /dev/null +++ b/testsuite/tests/backpack/should_compile/bkp41.stderr @@ -0,0 +1,13 @@ +[1 of 3] Processing impl + Instantiating impl + [1 of 2] Compiling A ( impl/A.hs, bkp41.out/impl/A.o ) + [2 of 2] Compiling B ( impl/B.hs, bkp41.out/impl/B.o ) +[2 of 3] Processing sig + [1 of 2] Compiling B[sig] ( sig/B.hsig, nothing ) + [2 of 2] Compiling App ( sig/App.hs, nothing ) +[3 of 3] Processing main + Instantiating main + [1 of 1] Including sig[B=impl:B] + Instantiating sig[B=impl:B] + [1 of 2] Compiling B[sig] ( sig/B.hsig, bkp41.out/sig/sig-HVnmSw44WZeBfwnUur4wzl/B.o ) + [2 of 2] Compiling App ( sig/App.hs, bkp41.out/sig/sig-HVnmSw44WZeBfwnUur4wzl/App.o ) From git at git.haskell.org Thu Dec 8 23:05:38 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Dec 2016 23:05:38 +0000 (UTC) Subject: [commit: ghc] master: Reduce qualification in error messages from signature matching. (617d57d) Message-ID: <20161208230538.E25033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/617d57d1166d67148f28401fabaf88295f1d3f06/ghc >--------------------------------------------------------------- commit 617d57d1166d67148f28401fabaf88295f1d3f06 Author: Edward Z. Yang Date: Wed Dec 7 23:07:19 2016 -0800 Reduce qualification in error messages from signature matching. Summary: Previously, we always qualified names, even if they were defined in the modules we were matching. Adding the exports of the implementing module into the RdrEnv greatly reduces the amount of qualification (although we still can't qualify things that the signature *imported*.) Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2803 >--------------------------------------------------------------- 617d57d1166d67148f28401fabaf88295f1d3f06 compiler/typecheck/TcBackpack.hs | 7 +++++++ testsuite/tests/backpack/should_fail/bkpfail06.stderr | 8 ++++---- testsuite/tests/backpack/should_fail/bkpfail07.stderr | 8 ++++---- testsuite/tests/backpack/should_fail/bkpfail10.stderr | 12 ++++++------ testsuite/tests/backpack/should_fail/bkpfail11.stderr | 5 ++--- testsuite/tests/backpack/should_fail/bkpfail12.stderr | 6 +++--- testsuite/tests/backpack/should_fail/bkpfail13.stderr | 6 +++--- testsuite/tests/backpack/should_fail/bkpfail14.stderr | 6 +++--- testsuite/tests/backpack/should_fail/bkpfail15.stderr | 6 +++--- testsuite/tests/backpack/should_fail/bkpfail17.stderr | 9 ++++----- testsuite/tests/backpack/should_fail/bkpfail22.stderr | 6 +++--- testsuite/tests/backpack/should_fail/bkpfail23.stderr | 8 ++++---- testsuite/tests/backpack/should_fail/bkpfail25.stderr | 6 +++--- testsuite/tests/backpack/should_fail/bkpfail26.stderr | 6 +++--- testsuite/tests/backpack/should_fail/bkpfail27.stderr | 6 +++--- 15 files changed, 55 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 617d57d1166d67148f28401fabaf88295f1d3f06 From git at git.haskell.org Thu Dec 8 23:45:10 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Dec 2016 23:45:10 +0000 (UTC) Subject: [commit: ghc] master: hschooks.c: Fix long line (58c290a) Message-ID: <20161208234510.2B3C83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/58c290a6523c68a42460964325a0fcd277d2a673/ghc >--------------------------------------------------------------- commit 58c290a6523c68a42460964325a0fcd277d2a673 Author: Ben Gamari Date: Thu Dec 8 15:55:15 2016 -0500 hschooks.c: Fix long line >--------------------------------------------------------------- 58c290a6523c68a42460964325a0fcd277d2a673 ghc/hschooks.c | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc/hschooks.c b/ghc/hschooks.c index c74830d..ace28be 100644 --- a/ghc/hschooks.c +++ b/ghc/hschooks.c @@ -54,7 +54,10 @@ defaultsHook (void) void StackOverflowHook (StgWord stack_size) /* in bytes */ { - fprintf(stderr, "GHC stack-space overflow: current limit is %zu bytes.\nUse the `-K' option to increase it.\n", (size_t)stack_size); + fprintf(stderr, + "GHC stack-space overflow: current limit is %zu bytes.\n" + "Use the `-K' option to increase it.\n", + (size_t) stack_size); } int main (int argc, char *argv[]) From git at git.haskell.org Thu Dec 8 23:45:12 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Dec 2016 23:45:12 +0000 (UTC) Subject: [commit: ghc] master: nativeGen: Fix string merging on Windows (55361b3) Message-ID: <20161208234512.E07573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/55361b381d14d8752f00d90868fcbe82f86c6b2d/ghc >--------------------------------------------------------------- commit 55361b381d14d8752f00d90868fcbe82f86c6b2d Author: Ben Gamari Date: Thu Dec 8 16:33:42 2016 -0500 nativeGen: Fix string merging on Windows D1290 places string constants in the `.rodata.str` section with `aMS` section flags so that the linker can merge them. However, it seems that ld doesn't understand these flags. It appears that `gcc -fmerge-constants` uses the `dr` flags on Windows. Make GHC do the same. Test Plan: Validate on Windows Reviewers: xnyhps, austin, Phyx Reviewed By: Phyx Subscribers: thomie, trommler Differential Revision: https://phabricator.haskell.org/D2797 GHC Trac Issues: #9577 >--------------------------------------------------------------- 55361b381d14d8752f00d90868fcbe82f86c6b2d compiler/nativeGen/PprBase.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/compiler/nativeGen/PprBase.hs b/compiler/nativeGen/PprBase.hs index e7feb8a..10ed2fb 100644 --- a/compiler/nativeGen/PprBase.hs +++ b/compiler/nativeGen/PprBase.hs @@ -98,16 +98,19 @@ pprGNUSectionHeader t suffix = sdocWithDynFlags $ \dflags -> let splitSections = gopt Opt_SplitSections dflags subsection | splitSections = char '.' <> ppr suffix | otherwise = empty - in text ".section " <> ptext header <> subsection + in text ".section " <> ptext (header dflags) <> subsection where - header = case t of + header dflags = case t of Text -> sLit ".text" Data -> sLit ".data" ReadOnlyData -> sLit ".rodata" RelocatableReadOnlyData -> sLit ".data.rel.ro" UninitialisedData -> sLit ".bss" ReadOnlyData16 -> sLit ".rodata.cst16" - CString -> sLit ".rodata.str1.1,\"aMS\", at progbits,1" + CString + | OSMinGW32 <- platformOS (targetPlatform dflags) + -> sLit ".rdata,\"dr\"" + | otherwise -> sLit ".rodata.str1.1,\"aMS\", at progbits,1" OtherSection _ -> panic "PprBase.pprGNUSectionHeader: unknown section type" From git at git.haskell.org Thu Dec 8 23:45:15 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Dec 2016 23:45:15 +0000 (UTC) Subject: [commit: ghc] master: BlockId: remove BlockMap and BlockSet synonyms (2bb099e) Message-ID: <20161208234515.ACF633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2bb099e5ccd7255f9742cb8bc5d512cd92d035b6/ghc >--------------------------------------------------------------- commit 2bb099e5ccd7255f9742cb8bc5d512cd92d035b6 Author: Michal Terepeta Date: Thu Dec 8 16:34:10 2016 -0500 BlockId: remove BlockMap and BlockSet synonyms This continues removal of `BlockId` module in favor of Hoopl's `Label`. Most of the changes here are mechanical, apart from the orphan `Outputable` instances for `LabelMap` and `LabelSet`. For now I've moved them to `cmm/Hoopl`, since it's already trying to manage all imports from Hoopl (to avoid any collisions). Signed-off-by: Michal Terepeta Test Plan: validate Reviewers: bgamari, austin, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2800 >--------------------------------------------------------------- 2bb099e5ccd7255f9742cb8bc5d512cd92d035b6 compiler/cmm/BlockId.hs | 15 --------- compiler/cmm/Cmm.hs | 6 ++-- compiler/cmm/CmmBuildInfoTables.hs | 15 +++++---- compiler/cmm/CmmCommonBlockElim.hs | 8 ++--- compiler/cmm/CmmContFlowOpt.hs | 20 ++++++------ compiler/cmm/CmmLayoutStack.hs | 36 +++++++++++----------- compiler/cmm/CmmLint.hs | 5 ++- compiler/cmm/CmmLive.hs | 2 +- compiler/cmm/CmmProcPoint.hs | 10 +++--- compiler/cmm/CmmSink.hs | 7 ++--- compiler/cmm/CmmUtils.hs | 6 ++-- compiler/cmm/Hoopl.hs | 8 +++++ compiler/cmm/Hoopl/Dataflow.hs | 1 - compiler/nativeGen/AsmCodeGen.hs | 10 +++--- compiler/nativeGen/Instruction.hs | 9 +++--- compiler/nativeGen/NCGMonad.hs | 1 + compiler/nativeGen/PPC/Instr.hs | 5 +-- compiler/nativeGen/PPC/Ppr.hs | 4 +-- compiler/nativeGen/RegAlloc/Graph/Spill.hs | 1 + compiler/nativeGen/RegAlloc/Graph/SpillClean.hs | 1 + compiler/nativeGen/RegAlloc/Graph/SpillCost.hs | 2 +- .../nativeGen/RegAlloc/Linear/JoinToTargets.hs | 1 + compiler/nativeGen/RegAlloc/Linear/Main.hs | 1 + compiler/nativeGen/RegAlloc/Liveness.hs | 7 +++-- compiler/nativeGen/SPARC/Ppr.hs | 4 +-- compiler/nativeGen/X86/Instr.hs | 5 +-- compiler/nativeGen/X86/Ppr.hs | 4 +-- 27 files changed, 96 insertions(+), 98 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2bb099e5ccd7255f9742cb8bc5d512cd92d035b6 From git at git.haskell.org Thu Dec 8 23:45:18 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Dec 2016 23:45:18 +0000 (UTC) Subject: [commit: ghc] master: Update Windows GCC driver. (1e5b7d7) Message-ID: <20161208234518.644C53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1e5b7d701149dc20c9f92e722c32912c86d53081/ghc >--------------------------------------------------------------- commit 1e5b7d701149dc20c9f92e722c32912c86d53081 Author: Tamar Christina Date: Thu Dec 8 16:33:11 2016 -0500 Update Windows GCC driver. Test Plan: None really, as none of our tests cover this usage. Probably should add one.. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie, #ghc_windows_task_force Differential Revision: https://phabricator.haskell.org/D2810 GHC Trac Issues: #12871 >--------------------------------------------------------------- 1e5b7d701149dc20c9f92e722c32912c86d53081 driver/gcc/gcc.c | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/driver/gcc/gcc.c b/driver/gcc/gcc.c index 517b008..e66accb 100644 --- a/driver/gcc/gcc.c +++ b/driver/gcc/gcc.c @@ -48,11 +48,11 @@ int main(int argc, char** argv) { preArgv[0] = mkString("-B%s", binDir); preArgv[1] = mkString("-B%s/../lib", binDir); #ifdef __MINGW64__ - preArgv[2] = mkString("-B%s/../lib/gcc/x86_64-w64-mingw32/5.2.0", binDir); - preArgv[3] = mkString("-B%s/../libexec/gcc/x86_64-w64-mingw32/5.2.0", binDir); + preArgv[2] = mkString("-B%s/../lib/gcc/x86_64-w64-mingw32/6.2.0", binDir); + preArgv[3] = mkString("-B%s/../libexec/gcc/x86_64-w64-mingw32/6.2.0", binDir); #else - preArgv[2] = mkString("-B%s/../lib/gcc/i686-w64-mingw32/5.2.0", binDir); - preArgv[3] = mkString("-B%s/../libexec/gcc/i686-w64-mingw32/5.2.0", binDir); + preArgv[2] = mkString("-B%s/../lib/gcc/i686-w64-mingw32/6.2.0", binDir); + preArgv[3] = mkString("-B%s/../libexec/gcc/i686-w64-mingw32/6.2.0", binDir); #endif run(exePath, 4, preArgv, argc - 1, argv + 1); } From git at git.haskell.org Thu Dec 8 23:45:21 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Dec 2016 23:45:21 +0000 (UTC) Subject: [commit: ghc] master: rts/linker: Fix LoadArchive build on Windows (c766d53) Message-ID: <20161208234521.1C60F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c766d53f3d8b58567b3bacf36fd7b6509656b1fc/ghc >--------------------------------------------------------------- commit c766d53f3d8b58567b3bacf36fd7b6509656b1fc Author: Ben Gamari Date: Thu Dec 8 16:32:30 2016 -0500 rts/linker: Fix LoadArchive build on Windows Test Plan: Validate on Windows. Reviewers: austin, erikd, simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2798 GHC Trac Issues: #12388 >--------------------------------------------------------------- c766d53f3d8b58567b3bacf36fd7b6509656b1fc rts/linker/LoadArchive.c | 43 ++++++++++++++++++++++++------------------- rts/linker/PEi386.c | 2 +- 2 files changed, 25 insertions(+), 20 deletions(-) diff --git a/rts/linker/LoadArchive.c b/rts/linker/LoadArchive.c index 99d8fe4..7d9dc22 100644 --- a/rts/linker/LoadArchive.c +++ b/rts/linker/LoadArchive.c @@ -62,7 +62,7 @@ static StgBool loadFatArchive(char tmp[static 20], FILE* f, pathchar* path) /* search for the right arch */ int n = fread(tmp, 1, 12, f); if (n != 12) { - errorBelch("Failed reading arch from `%s'", path); + errorBelch("Failed reading arch from `%" PATH_FMT "'", path); return false; } cputype = read4Bytes(tmp); @@ -82,21 +82,21 @@ static StgBool loadFatArchive(char tmp[static 20], FILE* f, pathchar* path) /* Seek to the correct architecture */ int n = fseek(f, nfat_offset, SEEK_SET); if (n != 0) { - errorBelch("Failed to seek to arch in `%s'", path); + errorBelch("Failed to seek to arch in `%" PATH_FMT "'", path); return false; } /* Read the header */ n = fread(tmp, 1, 8, f); if (n != 8) { - errorBelch("Failed reading header from `%s'", path); + errorBelch("Failed reading header from `%" PATH_FMT "'", path); return false; } /* Check the magic number */ if (strncmp(tmp, "!\n", 8) != 0) { - errorBelch("couldn't find archive in `%s' at offset %d", path, - nfat_offset); + errorBelch("couldn't find archive in `%" PATH_FMT "'" + "at offset %d", path, nfat_offset); return false; } } @@ -126,12 +126,14 @@ static StgBool readThinArchiveMember(int n, int memberSize, pathchar* path, stgFree(dirName); member = pathopen(memberPath, WSTR("rb")); if (!member) { - errorBelch("loadObj: can't read thin archive `%s'", memberPath); + errorBelch("loadObj: can't read thin archive `%" PATH_FMT "'", + memberPath); goto inner_fail; } n = fread(image, 1, memberSize, member); if (n != memberSize) { - errorBelch("loadArchive: error whilst reading `%s'", fileName); + errorBelch("loadArchive: error whilst reading `%s'", + fileName); goto inner_fail; } has_succeeded = true; @@ -152,12 +154,12 @@ static StgBool checkFatArchive(char magic[static 20], FILE* f, pathchar* path) if (read4Bytes(magic) == FAT_MAGIC) success = loadFatArchive(magic, f, path); else - errorBelch("loadArchive: Neither an archive, nor a fat archive: `%s'", - path); + errorBelch("loadArchive: Neither an archive, nor a fat archive: " + "`%" PATH_FMT "'", path); #else (void)magic; (void)f; - errorBelch("loadArchive: Not an archive: `%s'", path); + errorBelch("loadArchive: Not an archive: `%" PATH_FMT "'", path); #endif return success; } @@ -186,21 +188,21 @@ lookupGNUArchiveIndex(int gnuFileIndexSize, char **fileName_, n = atoi(fileName + 1); if (gnuFileIndex == NULL) { errorBelch("loadArchive: GNU-variant filename " - "without an index while reading from `%s'", + "without an index while reading from `%" PATH_FMT "'", path); return false; } if (n < 0 || n > gnuFileIndexSize) { errorBelch("loadArchive: GNU-variant filename " "offset %d out of range [0..%d] " - "while reading filename from `%s'", + "while reading filename from `%" PATH_FMT "'", n, gnuFileIndexSize, path); return false; } if (n != 0 && gnuFileIndex[n - 1] != '\n') { errorBelch("loadArchive: GNU-variant filename offset " "%d invalid (range [0..%d]) while reading " - "filename from `%s'", + "filename from `%" PATH_FMT "'", n, gnuFileIndexSize, path); return false; } @@ -227,8 +229,9 @@ lookupGNUArchiveIndex(int gnuFileIndexSize, char **fileName_, *thisFileNameSize = 0; } else { - errorBelch("loadArchive: invalid GNU-variant filename `%.16s'" - " while reading filename from `%s'", fileName, path); + errorBelch("loadArchive: invalid GNU-variant filename `%.16s' " + "while reading filename from `%" PATH_FMT "'", + fileName, path); return false; } @@ -394,7 +397,8 @@ static HsInt loadArchive_ (pathchar *path) } n = fread(fileName, 1, thisFileNameSize, f); if (n != thisFileNameSize) { - errorBelch("Failed reading filename from `%s'", path); + errorBelch("Failed reading filename from `%" PATH_FMT "'", + path); goto fail; } fileName[thisFileNameSize] = 0; @@ -404,7 +408,7 @@ static HsInt loadArchive_ (pathchar *path) thisFileNameSize = strlen(fileName); } else { errorBelch("BSD-variant filename size not found " - "while reading filename from `%s'", path); + "while reading filename from `%" PATH_FMT "'", path); goto fail; } } @@ -555,7 +559,7 @@ static HsInt loadArchive_ (pathchar *path) else if (isGnuIndex) { if (gnuFileIndex != NULL) { FAIL("GNU-variant index found, but already have an index, \ -while reading filename from `%s'", path); +while reading filename from `%" PATH_FMT "'", path); } DEBUG_LOG("Found GNU-variant file index\n"); #if RTS_LINKER_USE_MMAP @@ -587,7 +591,8 @@ while reading filename from `%s'", path); #endif } else { - DEBUG_LOG("'%s' does not appear to be an object file\n", fileName); + DEBUG_LOG("`%s' does not appear to be an object file\n", + fileName); if (!isThin || thisFileNameSize == 0) { n = fseek(f, memberSize, SEEK_CUR); if (n != 0) diff --git a/rts/linker/PEi386.c b/rts/linker/PEi386.c index b7db10b..6cd4861 100644 --- a/rts/linker/PEi386.c +++ b/rts/linker/PEi386.c @@ -1158,7 +1158,7 @@ ocGetNames_PEi386 ( ObjectCode* oc ) if (addr != NULL || isWeak == HS_BOOL_TRUE) { /* debugBelch("addSymbol %p `%s' Weak:%lld \n", addr, sname, isWeak); */ - IF_DEBUG(linker, debugBelch("addSymbol %p `%s'\n", addr,sname);) + IF_DEBUG(linker, debugBelch("addSymbol %p `%s'\n", addr,sname)); ASSERT(i >= 0 && i < oc->n_symbols); /* cstring_from_COFF_symbol_name always succeeds. */ oc->symbols[i] = (SymbolName*)sname; From git at git.haskell.org Thu Dec 8 23:45:24 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Dec 2016 23:45:24 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add test for #10249 (6889400) Message-ID: <20161208234524.5640E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6889400bd5ce6b481844fe5cfa7c9256ff5cd52f/ghc >--------------------------------------------------------------- commit 6889400bd5ce6b481844fe5cfa7c9256ff5cd52f Author: Ben Gamari Date: Thu Dec 8 16:32:55 2016 -0500 testsuite: Add test for #10249 Test Plan: Validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2794 GHC Trac Issues: #10249 >--------------------------------------------------------------- 6889400bd5ce6b481844fe5cfa7c9256ff5cd52f testsuite/tests/ghci/scripts/T10249.script | 1 + testsuite/tests/ghci/scripts/T10249.stderr | 8 ++++++++ testsuite/tests/ghci/scripts/all.T | 1 + 3 files changed, 10 insertions(+) diff --git a/testsuite/tests/ghci/scripts/T10249.script b/testsuite/tests/ghci/scripts/T10249.script new file mode 100644 index 0000000..c9cdc63 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T10249.script @@ -0,0 +1 @@ +_ \ No newline at end of file diff --git a/testsuite/tests/ghci/scripts/T10249.stderr b/testsuite/tests/ghci/scripts/T10249.stderr new file mode 100644 index 0000000..ade9950 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T10249.stderr @@ -0,0 +1,8 @@ + +:1:1: error: + • Found hole: _ :: t + Where: ‘t’ is a rigid type variable bound by + the inferred type of it :: t at :1:1 + • In the expression: _ + In an equation for ‘it’: it = _ + • Relevant bindings include it :: t (bound at :1:1) diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 53cb1e3..b89d1c4 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -268,3 +268,4 @@ test('T12523', normal, ghci_script, ['T12523.script']) test('T12024', normal, ghci_script, ['T12024.script']) test('T12447', expect_broken(12447), ghci_script, ['T12447.script']) test('T12550', expect_broken(12550), ghci_script, ['T12550.script']) +test('T10249', normal, ghci_script, ['T10249.script']) From git at git.haskell.org Thu Dec 8 23:45:27 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Dec 2016 23:45:27 +0000 (UTC) Subject: [commit: ghc] master: arclint: Lint cabal files (5063edb) Message-ID: <20161208234527.0C4923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5063edbc342467d451519c7cee38d0a2cc8b3f4d/ghc >--------------------------------------------------------------- commit 5063edbc342467d451519c7cee38d0a2cc8b3f4d Author: Ben Gamari Date: Thu Dec 8 16:31:49 2016 -0500 arclint: Lint cabal files Test Plan: Try linting a cabal file with trailing whitespace Reviewers: austin Subscribers: thomie, alanz Differential Revision: https://phabricator.haskell.org/D2799 >--------------------------------------------------------------- 5063edbc342467d451519c7cee38d0a2cc8b3f4d .arclint | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) diff --git a/.arclint b/.arclint index 70767e9..7eaced6 100644 --- a/.arclint +++ b/.arclint @@ -53,6 +53,22 @@ "2": "disabled" } }, + "cabal": { + "type": "text", + "include": ["(\\.cabal(\\.in)?$)"], + "severity": { + "5": "disabled", + "2": "warning" + } + }, + "other-text": { + "type": "text", + "include": ["(.travis.yml?)", "(.md$)", "(.txt$)"], + "severity": { + "5": "disabled", + "2": "warning" + } + }, "check-binaries": { "type": "external-json", "external-json.script": "python .arc-linters/check-binaries.py" From git at git.haskell.org Fri Dec 9 04:06:17 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Dec 2016 04:06:17 +0000 (UTC) Subject: [commit: ghc] master: rts/PosixSource.h: Define __USE_MINGW_ANSI_STDIO on Windows (6da6253) Message-ID: <20161209040617.7BA583A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6da62535469149d69ec98674db1c51dbde0efab1/ghc >--------------------------------------------------------------- commit 6da62535469149d69ec98674db1c51dbde0efab1 Author: Ben Gamari Date: Thu Dec 8 23:05:21 2016 -0500 rts/PosixSource.h: Define __USE_MINGW_ANSI_STDIO on Windows This was removed in 8dc72f3c33b0e724ddb690c9d494969980c10afd which cleaned up PosixSource.h. Strangely, this only started breaking for me now. Test Plan: Validate on Windows Reviewers: simonmar, erikd, austin, Phyx Reviewed By: Phyx Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2812 GHC Trac Issues: #12951 >--------------------------------------------------------------- 6da62535469149d69ec98674db1c51dbde0efab1 rts/PosixSource.h | 13 +++++++++++++ 1 file changed, 13 insertions(+) diff --git a/rts/PosixSource.h b/rts/PosixSource.h index 0ba74df..edf16b5 100644 --- a/rts/PosixSource.h +++ b/rts/PosixSource.h @@ -38,4 +38,17 @@ #define _XOPEN_SOURCE 700 #endif +#if defined(mingw32_HOST_OS) +/* Without this gcc will warn about %ull and the like since some msvcrt versions + do not support them. See + https://sourceforge.net/p/mingw-w64/mailman/message/28557333/ + + Note that this is implied by _POSIX_C_SOURCE in the msys2 toolchain that we + now use. However, we retain this explicit #define to preserve the ability to + bootstrap GHC with compilers still using msys (e.g. GHC 7.10.1 and 7.10.2). + This can be removed in for GHC 8.4. See #12951. + */ +#define __USE_MINGW_ANSI_STDIO 1 +#endif + #endif /* POSIXSOURCE_H */ From git at git.haskell.org Fri Dec 9 13:56:43 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Dec 2016 13:56:43 +0000 (UTC) Subject: [commit: ghc] master: Disambiguate reified closed type family kinds in TH (f65ff2c) Message-ID: <20161209135643.37EC03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f65ff2c4c9b60e370a722ac7572186816e23e573/ghc >--------------------------------------------------------------- commit f65ff2c4c9b60e370a722ac7572186816e23e573 Author: Ryan Scott Date: Fri Dec 9 08:50:54 2016 -0500 Disambiguate reified closed type family kinds in TH Summary: A continuation of #8953. This fixes an oversight in which the left-hand sides of closed type families, when reified in Template Haskell, would not be given kind annotations, even when they are necessary for disambiguation purposes in the presence of `PolyKinds`. Fixes #8953 and #12646. Test Plan: ./validate Reviewers: hvr, bgamari, austin, goldfire Reviewed By: goldfire Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2795 GHC Trac Issues: #8953, #12646 >--------------------------------------------------------------- f65ff2c4c9b60e370a722ac7572186816e23e573 compiler/typecheck/TcSplice.hs | 11 ++++++++--- docs/users_guide/8.2.1-notes.rst | 5 +++++ testsuite/tests/th/T12646.hs | 16 ++++++++++++++++ testsuite/tests/th/T12646.stderr | 3 +++ testsuite/tests/th/T8884.stderr | 2 +- testsuite/tests/th/all.T | 1 + 6 files changed, 34 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcSplice.hs b/compiler/typecheck/TcSplice.hs index a0838ee..1e35eec 100644 --- a/compiler/typecheck/TcSplice.hs +++ b/compiler/typecheck/TcSplice.hs @@ -1357,11 +1357,16 @@ reifyThing thing = pprPanic "reifyThing" (pprTcTyThingCategory thing) ------------------------------------------- reifyAxBranch :: TyCon -> CoAxBranch -> TcM TH.TySynEqn -reifyAxBranch fam_tc (CoAxBranch { cab_lhs = args, cab_rhs = rhs }) +reifyAxBranch fam_tc (CoAxBranch { cab_lhs = lhs, cab_rhs = rhs }) -- remove kind patterns (#8884) - = do { args' <- mapM reifyType (filterOutInvisibleTypes fam_tc args) + = do { let lhs_types_only = filterOutInvisibleTypes fam_tc lhs + ; lhs' <- reifyTypes lhs_types_only + ; annot_th_lhs <- zipWith3M annotThType (mkIsPolyTvs fam_tvs) + lhs_types_only lhs' ; rhs' <- reifyType rhs - ; return (TH.TySynEqn args' rhs') } + ; return (TH.TySynEqn annot_th_lhs rhs') } + where + fam_tvs = filterOutInvisibleTyVars fam_tc (tyConTyVars fam_tc) reifyTyCon :: TyCon -> TcM TH.Info reifyTyCon tc diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index 42a1ded..ea22d4f 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -124,6 +124,11 @@ Template Haskell - Make quoting and reification return the same types. (:ghc-ticket:`11629`) +- More kind annotations appear in the left-hand sides of reified closed + type family equations, in order to disambiguate types that would otherwise + be ambiguous in the presence of :ghc-flag:`-XPolyKinds`. + (:ghc-ticket:`12646`) + Runtime system ~~~~~~~~~~~~~~ diff --git a/testsuite/tests/th/T12646.hs b/testsuite/tests/th/T12646.hs new file mode 100644 index 0000000..197d59e --- /dev/null +++ b/testsuite/tests/th/T12646.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE TypeFamilies #-} +module T12646 where + +import Language.Haskell.TH +import System.IO + +type family F (a :: k) :: * where + F (a :: * -> *) = Int + F (a :: k) = Char + +$(do info <- reify ''F + runIO $ putStrLn $ pprint info + runIO $ hFlush stdout + return []) diff --git a/testsuite/tests/th/T12646.stderr b/testsuite/tests/th/T12646.stderr new file mode 100644 index 0000000..647ccd6 --- /dev/null +++ b/testsuite/tests/th/T12646.stderr @@ -0,0 +1,3 @@ +type family T12646.F (a_0 :: k_1) :: * where + T12646.F (a_2 :: * -> *) = GHC.Types.Int + T12646.F (a_3 :: k_4) = GHC.Types.Char diff --git a/testsuite/tests/th/T8884.stderr b/testsuite/tests/th/T8884.stderr index 28be299..022776e 100644 --- a/testsuite/tests/th/T8884.stderr +++ b/testsuite/tests/th/T8884.stderr @@ -1,4 +1,4 @@ type family T8884.Foo (a_0 :: k_1) = (r_2 :: k_1) | r_2 -> k_1 a_0 where - T8884.Foo x_3 = x_3 + T8884.Foo (x_3 :: k_4) = x_3 type family T8884.Baz (a_0 :: k_1) = (r_2 :: k_1) | r_2 -> k_1 a_0 type instance T8884.Baz (x_0 :: k_1) = x_0 diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index b96ea78..b144419 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -440,6 +440,7 @@ test('T12478_3', omit_ways(['ghci']), compile, ['-v0']) test('T12478_4', omit_ways(['ghci']), compile_fail, ['-v0']) test('T12513', omit_ways(['ghci']), compile_fail, ['-v0']) test('T12530', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques']) +test('T12646', normal, compile, ['-v0']) test('T12788', extra_clean(['T12788_Lib.hi', 'T12788_Lib.o']), multimod_compile_fail, ['T12788.hs', '-v0 ' + config.ghc_th_way_flags]) From git at git.haskell.org Fri Dec 9 16:17:53 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Dec 2016 16:17:53 +0000 (UTC) Subject: [commit: ghc] master: Bump haddock submodule (61932cd) Message-ID: <20161209161753.94E0B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/61932cd3eb0d5d22cb35d118fb9f87298881cd77/ghc >--------------------------------------------------------------- commit 61932cd3eb0d5d22cb35d118fb9f87298881cd77 Author: Ben Gamari Date: Fri Dec 9 10:26:07 2016 -0500 Bump haddock submodule Fixes Windows build. >--------------------------------------------------------------- 61932cd3eb0d5d22cb35d118fb9f87298881cd77 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 1dcefad..a5946c0 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 1dcefaddc52d968b20bb6107d620e1e0c6839970 +Subproject commit a5946c015e372750fd8d2054bb8a7e975149c9cc From git at git.haskell.org Fri Dec 9 16:17:56 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Dec 2016 16:17:56 +0000 (UTC) Subject: [commit: ghc] master: Scrutinee Constant Folding (d3b546b) Message-ID: <20161209161756.C71323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d3b546b1a6058f26d5659c7f2000a7b25b7ea2ba/ghc >--------------------------------------------------------------- commit d3b546b1a6058f26d5659c7f2000a7b25b7ea2ba Author: Sylvain Henry Date: Fri Dec 9 10:26:34 2016 -0500 Scrutinee Constant Folding This patch introduces new rules to perform constant folding through case-expressions. E.g., ``` case t -# 10# of _ { ===> case t of _ { 5# -> e1 15# -> e1 8# -> e2 18# -> e2 DEFAULT -> e DEFAULT -> e ``` The initial motivation is that it allows "Merge Nested Cases" optimization to kick in and to further simplify the code (see Trac #12877). Currently we recognize the following operations for Word# and Int#: Add, Sub, Xor, Not and Negate (for Int# only). Test Plan: validate Reviewers: simonpj, austin, bgamari Reviewed By: simonpj, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2762 GHC Trac Issues: #12877 >--------------------------------------------------------------- d3b546b1a6058f26d5659c7f2000a7b25b7ea2ba compiler/basicTypes/Literal.hs | 41 +++++++-- compiler/main/DynFlags.hs | 3 + compiler/prelude/PrelRules.hs | 57 +++++++++++- compiler/simplCore/SimplUtils.hs | 76 +++++++++++++++- docs/users_guide/using-optimisation.rst | 21 ++++- testsuite/tests/perf/compiler/T12877.hs | 117 +++++++++++++++++++++++++ testsuite/tests/perf/compiler/T12877.stdout | 1 + testsuite/tests/perf/compiler/all.T | 13 +++ utils/mkUserGuidePart/Options/Optimizations.hs | 5 ++ 9 files changed, 322 insertions(+), 12 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d3b546b1a6058f26d5659c7f2000a7b25b7ea2ba From git at git.haskell.org Fri Dec 9 16:17:59 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Dec 2016 16:17:59 +0000 (UTC) Subject: [commit: ghc] master: Disable colors unless printing to stderr (cee72d5) Message-ID: <20161209161759.890123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cee72d5c3c53863bd4fc9f324a93c322448e038e/ghc >--------------------------------------------------------------- commit cee72d5c3c53863bd4fc9f324a93c322448e038e Author: Phil Ruffwind Date: Fri Dec 9 10:28:25 2016 -0500 Disable colors unless printing to stderr Only print colors when mkLocMessageAnn is called directly from defaultLogAction. This prevents ANSI error codes from cluttering up the dump files. Test Plan: validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2792 GHC Trac Issues: #12927 >--------------------------------------------------------------- cee72d5c3c53863bd4fc9f324a93c322448e038e compiler/main/DynFlags.hs | 2 +- compiler/main/ErrUtils.hs | 33 ++++++++++++---------- compiler/utils/Outputable.hs | 66 +++++++++++++++++++++++++++----------------- 3 files changed, 60 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc cee72d5c3c53863bd4fc9f324a93c322448e038e From git at git.haskell.org Fri Dec 9 16:18:02 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Dec 2016 16:18:02 +0000 (UTC) Subject: [commit: ghc] master: Export `warningGroups' and `warningHierarchies' (1c296c0) Message-ID: <20161209161802.4C0A73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1c296c0c23bb058e44f4c8072fbbb0c405bfa0db/ghc >--------------------------------------------------------------- commit 1c296c0c23bb058e44f4c8072fbbb0c405bfa0db Author: Sylvain Henry Date: Fri Dec 9 10:28:45 2016 -0500 Export `warningGroups' and `warningHierarchies' Reviewers: austin, mpickering, bgamari Reviewed By: mpickering, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2806 >--------------------------------------------------------------- 1c296c0c23bb058e44f4c8072fbbb0c405bfa0db compiler/main/DynFlags.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index d9ffa82..3237a0a 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -28,6 +28,7 @@ module DynFlags ( FatalMessager, LogAction, FlushOut(..), FlushErr(..), ProfAuto(..), glasgowExtsFlags, + warningGroups, warningHierarchies, dopt, dopt_set, dopt_unset, gopt, gopt_set, gopt_unset, setGeneralFlag', unSetGeneralFlag', wopt, wopt_set, wopt_unset, From git at git.haskell.org Fri Dec 9 22:04:03 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Dec 2016 22:04:03 +0000 (UTC) Subject: [commit: ghc] master: testsuite: make tests respond to SIGINT properly (ca593c7) Message-ID: <20161209220403.020A73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ca593c7d55f0e120f322faf74c39fd4d978a6c1d/ghc >--------------------------------------------------------------- commit ca593c7d55f0e120f322faf74c39fd4d978a6c1d Author: Phil Ruffwind Date: Fri Dec 9 15:42:36 2016 -0500 testsuite: make tests respond to SIGINT properly The `std*_buffer` need to be bytes to avoid breaking Python 3. Also, using a blanket `except` in Python without specifying the exception types will catch special exceptions such as `KeyboardInterrupt`, which can prevent the program from being interrupted properly. Test Plan: validate Reviewers: thomie, austin, bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D2805 >--------------------------------------------------------------- ca593c7d55f0e120f322faf74c39fd4d978a6c1d testsuite/driver/testlib.py | 22 +++++++++------------- 1 file changed, 9 insertions(+), 13 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 7e7d994..5b582e1 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -24,11 +24,6 @@ from testglobals import * from testutil import * from extra_files import extra_src_files -try: - basestring -except: # Python 3 - basestring = (str,bytes) - if config.use_threads: import threading try: @@ -554,7 +549,8 @@ def join_normalisers(*a): Taken from http://stackoverflow.com/a/2158532/946226 """ for el in l: - if isinstance(el, collections.Iterable) and not isinstance(el, basestring): + if (isinstance(el, collections.Iterable) + and not isinstance(el, (bytes, str))): for sub in flatten(el): yield sub else: @@ -833,7 +829,7 @@ def do_test(name, way, func, args, files): try: result = func(*[name,way] + args) - except: + except Exception: pass if opts.expect not in ['pass', 'fail', 'missing-lib']: @@ -841,7 +837,7 @@ def do_test(name, way, func, args, files): try: passFail = result['passFail'] - except: + except (KeyError, TypeError): passFail = 'No passFail found' directory = re.sub('^\\.[/\\\\]', '', opts.testdir) @@ -882,7 +878,7 @@ def badResult(result): if result['passFail'] == 'pass': return False return True - except: + except (KeyError, TypeError): return True def passed(): @@ -1403,7 +1399,7 @@ def read_no_crs(file): # See Note [Universal newlines]. with io.open(file, 'r', encoding='utf8', errors='replace', newline=None) as h: str = h.read() - except: + except Exception: # On Windows, if the program fails very early, it seems the # files stdout/stderr are redirected to may not get created pass @@ -1724,7 +1720,7 @@ def if_verbose_dump( n, f ): try: with io.open(f) as file: print(file.read()) - except: + except Exception: print('') def runCmd(cmd, stdin=None, stdout=None, stderr=None, timeout_multiplier=1.0): @@ -1747,8 +1743,8 @@ def runCmd(cmd, stdin=None, stdout=None, stderr=None, timeout_multiplier=1.0): with io.open(stdin, 'rb') as f: stdin_buffer = f.read() - stdout_buffer = '' - stderr_buffer = '' + stdout_buffer = b'' + stderr_buffer = b'' hStdErr = subprocess.PIPE if stderr is subprocess.STDOUT: From git at git.haskell.org Fri Dec 9 22:04:05 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Dec 2016 22:04:05 +0000 (UTC) Subject: [commit: ghc] master: Fix LLVM TBAA metadata (90fae01) Message-ID: <20161209220405.AEB3F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/90fae01c326bf8b0802b4e8968f84886be4e1380/ghc >--------------------------------------------------------------- commit 90fae01c326bf8b0802b4e8968f84886be4e1380 Author: Demi Obenour Date: Fri Dec 9 15:41:59 2016 -0500 Fix LLVM TBAA metadata Accesses through a Cmm local are currently reported as having the "other" type, which can only alias other "other" accesses. However, this assumption is incorrect, which can result in silent bad LLVM codegen. Fixes #9308. Fixes #9504. Test Plan: GHC CI Reviewers: rwbarton, austin, bgamari Reviewed By: bgamari Subscribers: michalt, thomie Differential Revision: https://phabricator.haskell.org/D2758 GHC Trac Issues: #9125, #9308, #9504 >--------------------------------------------------------------- 90fae01c326bf8b0802b4e8968f84886be4e1380 compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 6 ++---- compiler/llvmGen/LlvmCodeGen/Regs.hs | 14 ++++++-------- 2 files changed, 8 insertions(+), 12 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 7b610c0..d88d234 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -845,8 +845,7 @@ genStore addr@(CmmMachOp (MO_Sub _) [ -- generic case genStore addr val - = do other <- getTBAAMeta otherN - genStore_slow addr val other + = getTBAAMeta topN >>= genStore_slow addr val -- | CmmStore operation -- This is a special case for storing to a global register pointer @@ -1494,8 +1493,7 @@ genLoad atomic e@(CmmMachOp (MO_Sub _) [ -- generic case genLoad atomic e ty - = do other <- getTBAAMeta otherN - genLoad_slow atomic e ty other + = getTBAAMeta topN >>= genLoad_slow atomic e ty -- | Handle CmmLoad expression. -- This is a special case for loading from a global register pointer diff --git a/compiler/llvmGen/LlvmCodeGen/Regs.hs b/compiler/llvmGen/LlvmCodeGen/Regs.hs index 8ac4153..1ee9fc1 100644 --- a/compiler/llvmGen/LlvmCodeGen/Regs.hs +++ b/compiler/llvmGen/LlvmCodeGen/Regs.hs @@ -6,7 +6,7 @@ module LlvmCodeGen.Regs ( lmGlobalRegArg, lmGlobalRegVar, alwaysLive, - stgTBAA, baseN, stackN, heapN, rxN, otherN, tbaa, getTBAA + stgTBAA, baseN, stackN, heapN, rxN, topN, tbaa, getTBAA ) where #include "HsVersions.h" @@ -102,21 +102,19 @@ stgTBAA , (heapN, fsLit "heap", Just topN) , (rxN, fsLit "rx", Just heapN) , (baseN, fsLit "base", Just topN) - -- FIX: Not 100% sure about 'others' place. Might need to be under 'heap'. - -- OR I think the big thing is Sp is never aliased, so might want - -- to change the hieracy to have Sp on its own branch that is never - -- aliased (e.g never use top as a TBAA node). - , (otherN, fsLit "other", Just topN) + -- FIX: Not 100% sure if this heirarchy is complete. I think the big thing + -- is Sp is never aliased, so might want to change the hierarchy to have Sp + -- on its own branch that is never aliased (e.g never use top as a TBAA + -- node). ] -- | Id values -topN, stackN, heapN, rxN, baseN, otherN :: Unique +topN, stackN, heapN, rxN, baseN :: Unique topN = getUnique (fsLit "LlvmCodeGen.Regs.topN") stackN = getUnique (fsLit "LlvmCodeGen.Regs.stackN") heapN = getUnique (fsLit "LlvmCodeGen.Regs.heapN") rxN = getUnique (fsLit "LlvmCodeGen.Regs.rxN") baseN = getUnique (fsLit "LlvmCodeGen.Regs.baseN") -otherN = getUnique (fsLit "LlvmCodeGen.Regs.otherN") -- | The TBAA metadata identifier tbaa :: LMString From git at git.haskell.org Fri Dec 9 22:04:08 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Dec 2016 22:04:08 +0000 (UTC) Subject: [commit: ghc] master: Mark T12903 as broken on OS X (62418b8) Message-ID: <20161209220408.603163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/62418b878a1e57b6d187c4f98bf90f6cd64a58b6/ghc >--------------------------------------------------------------- commit 62418b878a1e57b6d187c4f98bf90f6cd64a58b6 Author: Ben Gamari Date: Fri Dec 9 16:38:10 2016 -0500 Mark T12903 as broken on OS X Something has recently broken it. See #12956. >--------------------------------------------------------------- 62418b878a1e57b6d187c4f98bf90f6cd64a58b6 testsuite/tests/rts/all.T | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index f9c4b8e..d05e0ea 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -375,5 +375,7 @@ test('numa001', [ extra_run_opts('8'), extra_ways(['debug_numa']) ] test('T12497', [ unless(opsys('mingw32'), skip) ], run_command, ['$MAKE -s --no-print-directory T12497']) -test('T12903', [ when(opsys('mingw32'), skip)], compile_and_run, ['']) +test('T12903', [when(opsys('mingw32'), skip), + when(opsys('darwin'), expect_broken(12956)], + compile_and_run, ['']) From git at git.haskell.org Fri Dec 9 22:04:11 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Dec 2016 22:04:11 +0000 (UTC) Subject: [commit: ghc] master: NCG: Implement trivColorable for PowerPC 64-bit (2823492) Message-ID: <20161209220411.1398A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2823492e88889d823a871c193af041ae91784524/ghc >--------------------------------------------------------------- commit 2823492e88889d823a871c193af041ae91784524 Author: Peter Trommler Date: Fri Dec 9 15:42:11 2016 -0500 NCG: Implement trivColorable for PowerPC 64-bit Define constants for 64-bit PowerPC in graph coloring register allocator. Test Plan: ./validate Reviewers: simonmar, austin, erikd, bgamari, hvr Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2791 >--------------------------------------------------------------- 2823492e88889d823a871c193af041ae91784524 compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs b/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs index a40bec1..81e0c5e 100644 --- a/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs +++ b/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs @@ -111,7 +111,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts excl ArchPPC -> 16 ArchSPARC -> 14 ArchSPARC64 -> panic "trivColorable ArchSPARC64" - ArchPPC_64 _ -> panic "trivColorable ArchPPC_64" + ArchPPC_64 _ -> 15 ArchARM _ _ _ -> panic "trivColorable ArchARM" ArchARM64 -> panic "trivColorable ArchARM64" ArchAlpha -> panic "trivColorable ArchAlpha" @@ -137,7 +137,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclus ArchPPC -> 0 ArchSPARC -> 22 ArchSPARC64 -> panic "trivColorable ArchSPARC64" - ArchPPC_64 _ -> panic "trivColorable ArchPPC_64" + ArchPPC_64 _ -> 0 ArchARM _ _ _ -> panic "trivColorable ArchARM" ArchARM64 -> panic "trivColorable ArchARM64" ArchAlpha -> panic "trivColorable ArchAlpha" @@ -163,7 +163,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclu ArchPPC -> 26 ArchSPARC -> 11 ArchSPARC64 -> panic "trivColorable ArchSPARC64" - ArchPPC_64 _ -> panic "trivColorable ArchPPC_64" + ArchPPC_64 _ -> 20 ArchARM _ _ _ -> panic "trivColorable ArchARM" ArchARM64 -> panic "trivColorable ArchARM64" ArchAlpha -> panic "trivColorable ArchAlpha" @@ -189,7 +189,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcDoubleSSE conflicts ex ArchPPC -> 0 ArchSPARC -> 0 ArchSPARC64 -> panic "trivColorable ArchSPARC64" - ArchPPC_64 _ -> panic "trivColorable ArchPPC_64" + ArchPPC_64 _ -> 0 ArchARM _ _ _ -> panic "trivColorable ArchARM" ArchARM64 -> panic "trivColorable ArchARM64" ArchAlpha -> panic "trivColorable ArchAlpha" From git at git.haskell.org Fri Dec 9 22:04:13 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Dec 2016 22:04:13 +0000 (UTC) Subject: [commit: ghc] master: Rename TH constructors for deriving strategies (5349d64) Message-ID: <20161209220413.D8A823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5349d648fd7af3f50953e8594b3d148ab073017f/ghc >--------------------------------------------------------------- commit 5349d648fd7af3f50953e8594b3d148ab073017f Author: Ryan Scott Date: Fri Dec 9 15:44:15 2016 -0500 Rename TH constructors for deriving strategies After talking to Richard, he and I concluded that choosing the rather common name `Newtype` to represent the corresponding deriving strategy in Template Haskell was a poor choice of name. I've opted to rename it to something less common (`NewtypeStrategy`) while we still have time. I also renamed the corrsponding datatype in the GHC internals so as to match it. Reviewers: austin, goldfire, hvr, bgamari Reviewed By: bgamari Subscribers: thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2814 GHC Trac Issues: #10598 >--------------------------------------------------------------- 5349d648fd7af3f50953e8594b3d148ab073017f compiler/basicTypes/BasicTypes.hs | 19 ++++++++++--------- compiler/deSugar/DsMeta.hs | 6 +++--- compiler/hsSyn/Convert.hs | 6 +++--- compiler/parser/Parser.y | 6 +++--- compiler/prelude/THNames.hs | 12 +++++++----- compiler/typecheck/TcDeriv.hs | 20 ++++++++++---------- compiler/typecheck/TcDerivUtils.hs | 6 +++--- .../template-haskell/Language/Haskell/TH/Ppr.hs | 6 +++--- .../template-haskell/Language/Haskell/TH/Syntax.hs | 6 +++--- testsuite/tests/th/T10598_TH.hs | 12 ++++++------ testsuite/tests/th/T10598_TH.stderr | 12 ++++++------ 11 files changed, 57 insertions(+), 54 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5349d648fd7af3f50953e8594b3d148ab073017f From git at git.haskell.org Fri Dec 9 22:04:16 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Dec 2016 22:04:16 +0000 (UTC) Subject: [commit: ghc] master: Ensure each test inherits the TEST_HC_OPTS (d1df8d1) Message-ID: <20161209220416.9ACD33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d1df8d1c16b8f5bdf14ae41f514e38699f953054/ghc >--------------------------------------------------------------- commit d1df8d1c16b8f5bdf14ae41f514e38699f953054 Author: Phil Ruffwind Date: Fri Dec 9 15:43:02 2016 -0500 Ensure each test inherits the TEST_HC_OPTS This is so that global test flags that control the error formatting are propagated correctly. This patch is kind of related to: D2718 The stderr for API annotations is ignored entirely now per @alanz's suggestion. Test Plan: validate Reviewers: thomie, alanz, austin, bgamari Reviewed By: bgamari Subscribers: alanz Differential Revision: https://phabricator.haskell.org/D2808 >--------------------------------------------------------------- d1df8d1c16b8f5bdf14ae41f514e38699f953054 testsuite/tests/driver/T1372/Makefile | 2 +- testsuite/tests/ghc-api/annotations/T10268.stderr | 9 --- testsuite/tests/ghc-api/annotations/T10276.stderr | 70 ---------------------- testsuite/tests/ghc-api/annotations/T10278.stderr | 12 ---- testsuite/tests/ghc-api/annotations/T10280.stderr | 8 --- testsuite/tests/ghc-api/annotations/T10312.stderr | 2 - testsuite/tests/ghc-api/annotations/T10313.stderr | 31 ---------- testsuite/tests/ghc-api/annotations/T10354.stderr | 3 - testsuite/tests/ghc-api/annotations/T10357.stderr | 37 ------------ testsuite/tests/ghc-api/annotations/T10399.stderr | 15 ----- testsuite/tests/ghc-api/annotations/T11018.stderr | 40 ------------- testsuite/tests/ghc-api/annotations/T11321.stderr | 3 - testsuite/tests/ghc-api/annotations/all.T | 56 ++++++++--------- testsuite/tests/ghc-api/apirecomp001/Makefile | 2 +- .../tests/ghc-api/apirecomp001/apirecomp001.stderr | 12 ++-- testsuite/tests/ghc-api/apirecomp001/myghc.hs | 6 +- 16 files changed, 40 insertions(+), 268 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d1df8d1c16b8f5bdf14ae41f514e38699f953054 From git at git.haskell.org Fri Dec 9 22:04:19 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Dec 2016 22:04:19 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Mark prog003 as broken on Windows (24a4fe2) Message-ID: <20161209220419.69F673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/24a4fe2925d66e50b4f5e66e7a5c1ca4a320bf88/ghc >--------------------------------------------------------------- commit 24a4fe2925d66e50b4f5e66e7a5c1ca4a320bf88 Author: Ben Gamari Date: Fri Dec 9 16:57:33 2016 -0500 testsuite: Mark prog003 as broken on Windows Due to #11317. >--------------------------------------------------------------- 24a4fe2925d66e50b4f5e66e7a5c1ca4a320bf88 testsuite/tests/ghci/prog003/prog003.T | 1 + 1 file changed, 1 insertion(+) diff --git a/testsuite/tests/ghci/prog003/prog003.T b/testsuite/tests/ghci/prog003/prog003.T index f6dc380..19551fd 100644 --- a/testsuite/tests/ghci/prog003/prog003.T +++ b/testsuite/tests/ghci/prog003/prog003.T @@ -1,6 +1,7 @@ test('prog003', [extra_clean(['D.hs', 'D.hi', 'C.hi', 'C.o', 'B.hi', 'B.o', 'A', 'A.hi', 'A.o', 'a.out']), + when(opsys('mingw32'), expect_broken(11317)), cmd_prefix('ghciWayFlags=' + config.ghci_way_flags)], ghci_script, ['prog003.script']) From git at git.haskell.org Sat Dec 10 03:33:20 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 10 Dec 2016 03:33:20 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Fix syntax error in rts/all.T (2618090) Message-ID: <20161210033320.238AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2618090b67e3df00bf126a77f883ffd65d258567/ghc >--------------------------------------------------------------- commit 2618090b67e3df00bf126a77f883ffd65d258567 Author: Ben Gamari Date: Fri Dec 9 21:55:34 2016 -0500 testsuite: Fix syntax error in rts/all.T Yet another reason why no change to too small to validate. Arg. >--------------------------------------------------------------- 2618090b67e3df00bf126a77f883ffd65d258567 testsuite/tests/rts/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index d05e0ea..5037c6b 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -376,6 +376,6 @@ test('T12497', [ unless(opsys('mingw32'), skip) ], run_command, ['$MAKE -s --no-print-directory T12497']) test('T12903', [when(opsys('mingw32'), skip), - when(opsys('darwin'), expect_broken(12956)], + when(opsys('darwin'), expect_broken(12956))], compile_and_run, ['']) From git at git.haskell.org Sat Dec 10 03:33:22 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 10 Dec 2016 03:33:22 +0000 (UTC) Subject: [commit: ghc] master: rts: Provide _lock_file in symbol table on Windows (17ac9b1) Message-ID: <20161210033322.CDB753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/17ac9b19438d5e8f6de33f99828e8c0e7c8c1129/ghc >--------------------------------------------------------------- commit 17ac9b19438d5e8f6de33f99828e8c0e7c8c1129 Author: Ben Gamari Date: Fri Dec 9 22:00:00 2016 -0500 rts: Provide _lock_file in symbol table on Windows Test Plan: Validate on Windows, ensure that linking works. Reviewers: Phyx, austin, erikd, simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2817 >--------------------------------------------------------------- 17ac9b19438d5e8f6de33f99828e8c0e7c8c1129 rts/RtsSymbols.c | 25 ++++++++++++++++++++++++- 1 file changed, 24 insertions(+), 1 deletion(-) diff --git a/rts/RtsSymbols.c b/rts/RtsSymbols.c index 6dc0b6f..fdfbba3 100644 --- a/rts/RtsSymbols.c +++ b/rts/RtsSymbols.c @@ -70,6 +70,27 @@ #define RTS_WIN64_ONLY(X) /**/ #endif +/* + * Note [Symbols for MinGW's printf] + * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + * + * The printf offered by Microsoft's libc implementation, msvcrt, is quite + * incomplete, lacking support for even %ull. Consequently mingw-w64 offers its + * own implementation which we enable. However, to be thread-safe the + * implementation uses _lock_file. This would be fine except msvcrt.dll doesn't + * export _lock_file, only numbered versions do (e.g. msvcrt90.dll). + * + * To work around this mingw-w64 packages a static archive of msvcrt which + * includes their own implementation of _lock_file. However, this means that + * the archive contains things which the dynamic library does not; consequently + * we need to ensure that the runtime linker provides this symbol. + * + * It's all just so terrible. + * + * See also: + * https://sourceforge.net/p/mingw-w64/wiki2/gnu%20printf/ + * https://sourceforge.net/p/mingw-w64/discussion/723797/thread/55520785/ + */ #define RTS_MINGW_ONLY_SYMBOLS \ SymI_HasProto(stg_asyncReadzh) \ SymI_HasProto(stg_asyncWritezh) \ @@ -84,7 +105,9 @@ RTS_WIN32_ONLY(SymI_HasProto(_imp___environ)) \ RTS_WIN64_ONLY(SymI_HasProto(__imp__environ)) \ RTS_WIN32_ONLY(SymI_HasProto(_imp___iob)) \ - RTS_WIN64_ONLY(SymI_HasProto(__iob_func)) + RTS_WIN64_ONLY(SymI_HasProto(__iob_func)) \ + /* see Note [Symbols for MinGW's printf] */ \ + SymI_HasProto(_lock_file) #define RTS_MINGW_COMPAT_SYMBOLS \ SymI_HasProto_deprecated(access) \ From git at git.haskell.org Sat Dec 10 20:34:10 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 10 Dec 2016 20:34:10 +0000 (UTC) Subject: [commit: ghc] master: Add `_unlock_file` to RTS symbols (0ac5a00) Message-ID: <20161210203410.652273A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0ac5a0082ae2840783b514f02f94ad0376bf8142/ghc >--------------------------------------------------------------- commit 0ac5a0082ae2840783b514f02f94ad0376bf8142 Author: Tamar Christina Date: Sat Dec 10 15:33:53 2016 -0500 Add `_unlock_file` to RTS symbols Reviewers: bgamari, austin, erikd, simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2818 >--------------------------------------------------------------- 0ac5a0082ae2840783b514f02f94ad0376bf8142 rts/RtsSymbols.c | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/rts/RtsSymbols.c b/rts/RtsSymbols.c index fdfbba3..8485530 100644 --- a/rts/RtsSymbols.c +++ b/rts/RtsSymbols.c @@ -107,7 +107,8 @@ RTS_WIN32_ONLY(SymI_HasProto(_imp___iob)) \ RTS_WIN64_ONLY(SymI_HasProto(__iob_func)) \ /* see Note [Symbols for MinGW's printf] */ \ - SymI_HasProto(_lock_file) + SymI_HasProto(_lock_file) \ + SymI_HasProto(_unlock_file) #define RTS_MINGW_COMPAT_SYMBOLS \ SymI_HasProto_deprecated(access) \ From git at git.haskell.org Sat Dec 10 21:14:30 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 10 Dec 2016 21:14:30 +0000 (UTC) Subject: [commit: ghc] master: Automate GCC driver wrapper (490b942) Message-ID: <20161210211430.896AA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/490b9429a8ed3c55d17bf0964fb14582eb206a3d/ghc >--------------------------------------------------------------- commit 490b9429a8ed3c55d17bf0964fb14582eb206a3d Author: Tamar Christina Date: Sat Dec 10 21:13:40 2016 +0000 Automate GCC driver wrapper Summary: Everytime we upgrade the GCC version this wrapper needed updating. This is a big fragile and we kept forgetting it. Instead automate it so we don't have to worry about it. Test Plan: ./validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie, #ghc_windows_task_force Differential Revision: https://phabricator.haskell.org/D2820 GHC Trac Issues: #12871 >--------------------------------------------------------------- 490b9429a8ed3c55d17bf0964fb14582eb206a3d driver/gcc/gcc.c | 15 +++++++++++---- 1 file changed, 11 insertions(+), 4 deletions(-) diff --git a/driver/gcc/gcc.c b/driver/gcc/gcc.c index e66accb..5c7cb15 100644 --- a/driver/gcc/gcc.c +++ b/driver/gcc/gcc.c @@ -17,6 +17,8 @@ int main(int argc, char** argv) { char *preArgv[4]; char *oldPath; char *newPath; + char *base; + char *version; int n; binDir = getExecutablePath(); @@ -42,18 +44,23 @@ int main(int argc, char** argv) { die("putenv failed\n"); } + /* GCC Version. */ + version = mkString("%d.%d.%d", __GNUC__, __GNUC_MINOR__, __GNUC_PATCHLEVEL__); + /* Without these -B args, gcc will still work. However, if you have a mingw installation in c:/mingw then it will use files from that in preference to the in-tree files. */ preArgv[0] = mkString("-B%s", binDir); preArgv[1] = mkString("-B%s/../lib", binDir); #ifdef __MINGW64__ - preArgv[2] = mkString("-B%s/../lib/gcc/x86_64-w64-mingw32/6.2.0", binDir); - preArgv[3] = mkString("-B%s/../libexec/gcc/x86_64-w64-mingw32/6.2.0", binDir); + base = mkString("x86_64-w64-mingw32"); #else - preArgv[2] = mkString("-B%s/../lib/gcc/i686-w64-mingw32/6.2.0", binDir); - preArgv[3] = mkString("-B%s/../libexec/gcc/i686-w64-mingw32/6.2.0", binDir); + base = mkString("i686-w64-mingw32"); #endif + + preArgv[2] = mkString("-B%s/../lib/gcc/%s/%s" , binDir, base, version); + preArgv[3] = mkString("-B%s/../libexec/gcc/%s/%s", binDir, base, version); + run(exePath, 4, preArgv, argc - 1, argv + 1); } From git at git.haskell.org Sun Dec 11 15:29:29 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 11 Dec 2016 15:29:29 +0000 (UTC) Subject: [commit: ghc] master: Make globals use sharedCAF (c3c7024) Message-ID: <20161211152929.1D50C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c3c702441137dc8f7ee0dd5ac313be96d625459a/ghc >--------------------------------------------------------------- commit c3c702441137dc8f7ee0dd5ac313be96d625459a Author: Moritz Angermann Date: Sun Dec 11 11:32:28 2016 +0000 Make globals use sharedCAF Summary: The use of globals is quite painful when multiple rts are loaded, e.g. when plugins are loaded, which bring in a second rts. The sharedCAF appraoch was employed for the FastStringTable; I've taken the libery to extend this to the other globals I could find. This is a reboot of D2575, that should hopefully not exhibit the same windows build issues. Reviewers: Phyx, simonmar, goldfire, bgamari, austin, hvr, erikd Reviewed By: Phyx, simonmar, bgamari Subscribers: mpickering, thomie Differential Revision: https://phabricator.haskell.org/D2773 >--------------------------------------------------------------- c3c702441137dc8f7ee0dd5ac313be96d625459a compiler/HsVersions.h | 16 +++++ compiler/ghci/Linker.hs | 44 ++++++------ compiler/main/DynFlags.hs | 16 ++++- compiler/main/StaticFlags.hs | 20 +++++- compiler/simplCore/CoreMonad.hs | 75 ++------------------ compiler/utils/FastString.hs | 7 -- compiler/utils/Util.hs | 34 ++++++++++ docs/users_guide/extending_ghc.rst | 13 ---- includes/rts/Globals.h | 27 +++++--- libraries/base/GHC/Conc/Sync.hs | 2 +- rts/Globals.c | 79 +++++++--------------- rts/RtsSymbols.c | 5 ++ testsuite/tests/plugins/LinkerTicklingPlugin.hs | 4 +- .../tests/plugins/annotation-plugin/SayAnnNames.hs | 1 - .../should_compile/T7702plugin/T7702Plugin.hs | 1 - 15 files changed, 161 insertions(+), 183 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c3c702441137dc8f7ee0dd5ac313be96d625459a From git at git.haskell.org Mon Dec 12 11:57:05 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Dec 2016 11:57:05 +0000 (UTC) Subject: [commit: ghc] master: Make dropDerivedSimples restore [WD] constraints (f1036ad) Message-ID: <20161212115705.551EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f1036ad80efb9cf80977fa234f8b9c7b23cc6835/ghc >--------------------------------------------------------------- commit f1036ad80efb9cf80977fa234f8b9c7b23cc6835 Author: Simon Peyton Jones Date: Fri Dec 9 17:37:28 2016 +0000 Make dropDerivedSimples restore [WD] constraints I'd forgotten to turn [W] + [D] constraints back into [WD] in dropDerivedSimples; and that led to Trac #12936. Fortunately the fix is simple. >--------------------------------------------------------------- f1036ad80efb9cf80977fa234f8b9c7b23cc6835 compiler/typecheck/TcRnTypes.hs | 18 +++++++++++-- compiler/utils/Bag.hs | 16 ++++++++++++ testsuite/tests/typecheck/should_compile/T12936.hs | 30 ++++++++++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 4 files changed, 63 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index a496d25..4833839 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -1740,8 +1740,22 @@ tyCoFVsOfBag tvs_of = foldrBag (unionFV . tvs_of) emptyFV -------------------------- dropDerivedSimples :: Cts -> Cts -dropDerivedSimples simples = filterBag isWantedCt simples - -- simples are all Wanted or Derived +-- Drop all Derived constraints, but make [W] back into [WD], +-- so that if we re-simplify these constraints we will get all +-- the right derived constraints re-generated. Forgetting this +-- step led to #12936 +dropDerivedSimples simples = mapMaybeBag dropDerivedCt simples + +dropDerivedCt :: Ct -> Maybe Ct +dropDerivedCt ct + = case ctEvFlavour ev of + Wanted WOnly -> Just (ct { cc_ev = ev_wd }) + Wanted _ -> Just ct + _ -> ASSERT( isDerivedCt ct ) Nothing + -- simples are all Wanted or Derived + where + ev = ctEvidence ct + ev_wd = ev { ctev_nosh = WDeriv } dropDerivedInsols :: Cts -> Cts -- See Note [Dropping derived constraints] diff --git a/compiler/utils/Bag.hs b/compiler/utils/Bag.hs index f2b1ead..5fd4ba3 100644 --- a/compiler/utils/Bag.hs +++ b/compiler/utils/Bag.hs @@ -18,6 +18,7 @@ module Bag ( concatBag, catBagMaybes, foldBag, foldrBag, foldlBag, isEmptyBag, isSingletonBag, consBag, snocBag, anyBag, listToBag, bagToList, mapAccumBagL, + concatMapBag, mapMaybeBag, foldrBagM, foldlBagM, mapBagM, mapBagM_, flatMapBagM, flatMapBagPairM, mapAndUnzipBagM, mapAccumBagLM, @@ -30,6 +31,7 @@ import Util import MonadUtils import Control.Monad import Data.Data +import Data.Maybe( mapMaybe ) import Data.List ( partition, mapAccumL ) import qualified Data.Foldable as Foldable @@ -216,6 +218,20 @@ mapBag f (UnitBag x) = UnitBag (f x) mapBag f (TwoBags b1 b2) = TwoBags (mapBag f b1) (mapBag f b2) mapBag f (ListBag xs) = ListBag (map f xs) +concatMapBag :: (a -> Bag b) -> Bag a -> Bag b +concatMapBag _ EmptyBag = EmptyBag +concatMapBag f (UnitBag x) = f x +concatMapBag f (TwoBags b1 b2) = unionBags (concatMapBag f b1) (concatMapBag f b2) +concatMapBag f (ListBag xs) = foldr (unionBags . f) emptyBag xs + +mapMaybeBag :: (a -> Maybe b) -> Bag a -> Bag b +mapMaybeBag _ EmptyBag = EmptyBag +mapMaybeBag f (UnitBag x) = case f x of + Nothing -> EmptyBag + Just y -> UnitBag y +mapMaybeBag f (TwoBags b1 b2) = unionBags (mapMaybeBag f b1) (mapMaybeBag f b2) +mapMaybeBag f (ListBag xs) = ListBag (mapMaybe f xs) + mapBagM :: Monad m => (a -> m b) -> Bag a -> m (Bag b) mapBagM _ EmptyBag = return EmptyBag mapBagM f (UnitBag x) = do r <- f x diff --git a/testsuite/tests/typecheck/should_compile/T12936.hs b/testsuite/tests/typecheck/should_compile/T12936.hs new file mode 100644 index 0000000..c4f9660 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T12936.hs @@ -0,0 +1,30 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE FunctionalDependencies #-} +{-# LANGUAGE MonomorphismRestriction #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE ScopedTypeVariables #-} +module Token where + +class S s t | s -> t + +m :: forall s t . S s t => s +m = undefined + +o :: forall s t . S s t => s -> s +o = undefined + +c :: forall s . s -> s -> s +c = undefined + +p :: forall s . S s () => s -> s +p d = f + where + + -- declaring either of these type signatures will cause the bug to go away + + -- f :: s + f = c d (o e) + + -- e :: s + e = c m m diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 088c6fa..8d25b3a 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -557,3 +557,4 @@ test('T12763', normal, compile, ['']) test('T12797', normal, compile, ['']) test('T12925', normal, compile, ['']) test('T12919', expect_broken(12919), compile, ['']) +test('T12936', normal, compile, ['']) From git at git.haskell.org Mon Dec 12 11:57:08 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Dec 2016 11:57:08 +0000 (UTC) Subject: [commit: ghc] master: Refactor pruning of implication constraints (818e027) Message-ID: <20161212115708.1EA4B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/818e027e2db2ac291c44a5e07ae151505f3908b8/ghc >--------------------------------------------------------------- commit 818e027e2db2ac291c44a5e07ae151505f3908b8 Author: Simon Peyton Jones Date: Fri Dec 9 17:32:07 2016 +0000 Refactor pruning of implication constraints We try to prune solved implication constraints, but it's a bit tricky because of our desire to correctly report unused 'givens'. This patch improves matters a bit... in tracig some other bug I saw lots of empty constraints lying around! >--------------------------------------------------------------- 818e027e2db2ac291c44a5e07ae151505f3908b8 compiler/typecheck/TcInstDcls.hs | 2 ++ compiler/typecheck/TcRnTypes.hs | 15 +++++++-- compiler/typecheck/TcSMonad.hs | 1 + compiler/typecheck/TcSimplify.hs | 71 +++++++++++++++++++++++++--------------- compiler/typecheck/TcUnify.hs | 1 + 5 files changed, 60 insertions(+), 30 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 818e027e2db2ac291c44a5e07ae151505f3908b8 From git at git.haskell.org Mon Dec 12 13:18:47 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Dec 2016 13:18:47 +0000 (UTC) Subject: [commit: ghc] wip/rae: Reshuffle levity polymorphism checks. (afb9c30) Message-ID: <20161212131847.9E8103A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/afb9c30bd16645b56189c6d1deb9db64e16b9136/ghc >--------------------------------------------------------------- commit afb9c30bd16645b56189c6d1deb9db64e16b9136 Author: Richard Eisenberg Date: Thu Nov 10 13:41:30 2016 -0500 Reshuffle levity polymorphism checks. Previously, GHC checked for bad levity polymorphism to the left of all arrows in data constructors. This was wrong, as reported in #12911 (where an example is also shown). The solution is to check each individual argument for bad levity polymorphism. Thus the check has been moved from TcValidity to TcTyClsDecls. A similar situation exists with pattern synonyms, also fixed here. This patch also nabs #12819 while I was in town. Test cases: typecheck/should_compile/T12911, patsyn/should_fail/T12819 >--------------------------------------------------------------- afb9c30bd16645b56189c6d1deb9db64e16b9136 compiler/typecheck/TcSigs.hs | 28 +++++++++++++++++----- compiler/typecheck/TcTyClsDecls.hs | 2 ++ compiler/typecheck/TcValidity.hs | 14 +---------- compiler/types/Type.hs | 5 ++-- testsuite/tests/patsyn/should_fail/T12819.hs | 9 +++++++ testsuite/tests/patsyn/should_fail/T12819.stderr | 3 +++ testsuite/tests/patsyn/should_fail/all.T | 1 + testsuite/tests/typecheck/should_compile/T12911.hs | 9 +++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 9 files changed, 51 insertions(+), 21 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc afb9c30bd16645b56189c6d1deb9db64e16b9136 From git at git.haskell.org Mon Dec 12 13:18:50 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Dec 2016 13:18:50 +0000 (UTC) Subject: [commit: ghc] wip/rae: Intermediate state toward new levity polymorphism (089b085) Message-ID: <20161212131850.780173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/089b085d9660d029663126148665b468809278d7/ghc >--------------------------------------------------------------- commit 089b085d9660d029663126148665b468809278d7 Author: Richard Eisenberg Date: Mon Dec 12 08:18:21 2016 -0500 Intermediate state toward new levity polymorphism >--------------------------------------------------------------- 089b085d9660d029663126148665b468809278d7 compiler/codeGen/StgCmm.hs | 5 +- compiler/codeGen/StgCmmClosure.hs | 4 +- compiler/codeGen/StgCmmForeign.hs | 3 +- compiler/codeGen/StgCmmUtils.hs | 6 +- compiler/coreSyn/CoreLint.hs | 15 +-- compiler/deSugar/DsForeign.hs | 5 +- compiler/ghci/ByteCodeGen.hs | 24 ++--- compiler/ghci/ByteCodeItbls.hs | 4 +- compiler/ghci/RtClosureInspect.hs | 21 ++-- compiler/iface/IfaceType.hs | 22 ++-- compiler/main/InteractiveEval.hs | 5 +- compiler/prelude/PrelNames.hs | 16 +-- compiler/prelude/TysPrim.hs | 52 ++++------ compiler/prelude/TysWiredIn.hs | 168 +++++++++++++++++++++--------- compiler/simplStg/RepType.hs | 208 ++++++++++++++++++++++++-------------- compiler/simplStg/UnariseStg.hs | 50 ++++----- compiler/stgSyn/StgLint.hs | 4 +- compiler/typecheck/TcErrors.hs | 15 +-- compiler/typecheck/TcHsSyn.hs | 102 ++++--------------- compiler/typecheck/TcHsType.hs | 13 ++- compiler/typecheck/TcMType.hs | 2 +- compiler/typecheck/TcSimplify.hs | 13 ++- compiler/types/FamInstEnv.hs | 2 - compiler/types/Kind.hs | 2 +- compiler/types/TyCoRep.hs | 6 +- compiler/types/TyCon.hs | 10 +- compiler/types/Type.hs | 5 +- libraries/ghc-prim/GHC/Types.hs | 16 +-- 28 files changed, 414 insertions(+), 384 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 089b085d9660d029663126148665b468809278d7 From git at git.haskell.org Mon Dec 12 13:18:55 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Dec 2016 13:18:55 +0000 (UTC) Subject: [commit: ghc] wip/rae's head updated: Intermediate state toward new levity polymorphism (089b085) Message-ID: <20161212131855.A22353A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/rae' now includes: 9bc2233 Fix typo in Data.Bitraverse Haddocks 31b5806 Clean up outdated comments in template-haskell changelog a33b498 Add template-haskell changelog note for #8761 5fdb854 s/Invisible/Inferred/g s/Visible/Required/g 4cc5a39 Refactor tcInferArgs and add comments. 8c1cedd Allow building static libs. da60e3e rts/Linker.c: Improve ugly C pre-processor hack 7843c71 Make T8761 deterministic, I hope ff1cc26 Don't run the run_command tests with ext-interp 82282e8 Remove some `undefined`s 60c24b2 Typos in user manual and code: recurisve -> recursive afa6e83 rts/Linker.c: Rename ONLY_USED_x86_64_HOST_ARCH macro bbf0aa2 Testsuite: never pick up .T files in .run directories 7593c2f Testsuite: report duplicate testnames when `make TEST=` 1f45bce Testsuite: remove one level of indentation [skip ci] 206b4a1 Testsuite: simplify extra_file handling bafd615 Testsuite: do not print timeout message 58f0086 Testsuite: open/close stdin/stdout/stderr explicitly d8e9b87 Testsuite: cleanup printing of summary 782cacf Testsuite: framework failure improvements (#11165) 6b3b631 Testsuite: run all indexed-types ways on ./validate --slow 0eb0378 Testsuite: do not add -debug explicitly in .T file 3fb9837 Testsuite: mark tests expect_broken af21e38 Don't omit any evidence bindings 23b80ac Deal correctly with unused imports for 'coerce' dc62a22 Wibble error message for #11471 dd92c67 Stop the simplifier from removing StaticPtr binds. 2e9079f Test Trac #12185 848e3ce Testsuite: fixes for python2.6 support 9a645a1 Refactor match to not use Unique order 8f7194f Double the file descriptor limit for openFile008 1084d37 Testsuite: use ignore_stderr/stdout instead of ignore_output 24194a6 Fix pretty-printer for IfaceCo e8d6271 Testsuite: do not depend on sys.stdout.encoding fb6e2c7 Delete Ord Unique 9854f14 Add a new determinism test b6b20a5 Reorganize some determinism tests 480e066 Remove ufmToList b8b3e30 Axe RecFlag on TyCons. 0701db1 Updates to handle new Cabal 430f5c8 Trac #11554 fix loopy GADTs 6a5d13c nativeGen: Allow -fregs-graph to be used f68d40c ghc-pkg: Drop trailing slashes in computing db paths f1e16e9 CmmExpr: remove unused `vgcFlag` function b65363d Fix check_uniques in non-unicode locale 0afc41b Testsuite: be less strict about topHandler03's stderr c27ce26 users-guide: Fix markup in release notes 81b437b Add NamedThing (GenLocated l e) instance b412d82 Allow one type signature for multiple pattern synonyms 6ba4197 rules/sphinx.mk: stop xelatex on error ee8d1fa Remove unused oc->isImportLib (#12230) 6377757 Linker: some extra debugging / logging cbfeff4 Remove uniqSetToList 0d522b8 Document some benign nondeterminism 0ab63cf Kill varEnvElts in seqDmdEnv 01f449f Fix 32-bit build failures 9031382 MkCore: Fix some note names a6819a0 base: Add release date to changelog bf7cbe7 users-guide: Note multiple pattern signature change in relnotes afec447 testsuite: Add testcase for #12355 2a3af15 Treat duplicate pattern synonym signatures as an error 3b2deca users-guide: Remove static field type from rts-flag 331febf CallArity: Use not . null instead of length > 0 0bd7c4b Enum: Ensure that operations on Word fuse 18e71e4 Revert "Fix 32-bit build failures" 890ec98 Revert "Linker: some extra debugging / logging" e10497b Kill some varEnvElts 85aa6ef Check generic-default method for ambiguity 1267048 Extra ASSERTs for nameModule 55e43a6 Use DVarEnv for vectInfoVar 5f79394 Delete out-of-date comment 895eefa Make unique auxiliary function names in deriving cbe30fd Tidy up tidying f2d36ea White space only 6cedef0 Test Trac #12133 27fc75b Document codegen nondeterminism 18b782e Kill varEnvElts in zonkEnvIds 1b058d4 Remove varEnvElts b7b130c Fix GetTime.c on Darwin with clock_gettime f560a03 Adds x86_64-apple-darwin14 target. 567dbd9 Have addModFinalizer expose the local type environment. 56f47d4 Mention addModFinalizer changes in release notes. 672314c Switch to LLVM version 3.8 b9cea81 Show testcase where demand analysis abortion code fails 979baec --without-libcharset disables the use of libcharset bedd620 Style changes for UniqFM 6ed7c47 Document some codegen nondeterminism 9858552 Use deterministic maps for FamInstEnv 34085b5 Correct the message displayed for syntax error (#12146) 64bce8c Add Note [FamInstEnv determinism] 6e280c2 Utils: Fix `lengthIs` and `lengthExceeds` for negative args 0481324 Use UniqDFM for InstEnv b8cd94d GHC.Stack.CCS: Fix typo in Haddocks 91fd87e FastString: Reduce allocations of concatFS 15751f2 FastString: Add IsString instance c4a9dca FastString: Supply mconcat implementation fc53d36 OccName: Implement startsWithUnderscore in terms of headFS eb3d659 OccName: Avoid re-encoding derived OccNames 4f21a51 Kill eltsUFM in classifyTyCons 6c7c193 DsExpr: Remove usage of concatFS in fingerprintName 0177c85 Testsuite: expose TEST_CC (path to gcc) f53d761 TysWiredIn: Use UniqFM lookup for built-in OccNames 9a3df1f check-api-annotations utility loads by filename 17d0b84 Add -package-env to the flags reference 372dbc4 Pretty: delete really old changelog 45d8f4e Demand analyser: Implement LetUp rule (#12370) 18ac80f tidyType: Rename variables of nested forall at once cd0750e tidyOccNames: Rename variables fairly 37aeff6 Added type family dependency to Data.Type.Bool.Not b35e01c Bring comments in TcGenGenerics up to date a9bc547 Log heap profiler samples to event log ffe4660 IfaceEnv: Only check for built-in OccNames if mod is GHC.Types 24f5f36 Binary: Use ByteString's copy in getBS 0f0cdb6 Bugfix for bug 11632: `readLitChar` should consume null characters 1ba79fa CodeGen: Way to dump cmm only once (#11717) 89a8be7 Pretty: remove a harmful $! (#12227) 5df92f6 hp2ps: fix invalid PostScript for names with parentheses d213ab3 Fix misspellings of the word "instance" in comments 3fa3fe8 Make DeriveFunctor work with unboxed tuples 514c4a4 Fix Template Haskell reification of unboxed tuple types 1fc41d3 Make okConIdOcc recognize unboxed tuples 0df3f4c Fix PDF build for the User's Guide. 98b2c50 Support SCC pragmas in declaration context e46b768 Make Data.{Bifoldable,Bitraversable} -XSafe 908f8e2 TcInteract: Add braces to matchClassInst trace output 8de6e13 Fix bytecode generator panic cac3fb0 Cleanup PosixSource.h a0f83a6 Data.Either: Add fromLeft and fromRight (#12402) 627c767 Update docs for partial type signatures (#12365) ed48098 InstEnv: Ensure that instance visibility check is lazy 9513fe6 Clean up interaction between name cache and built-in syntax a4f2b76 testsuite: Add regression test for #12381 93acc02 Add another testcase for #12082 cf989ff Compact Regions 83e4f49 Revert "Clean up interaction between name cache and built-in syntax" 714bebf Implement unboxed sum primitive type a09c0e3 Comments only 9c54185 Comments + tiny refactor of isNullarySrcDataCon 8d4760f Comments re ApThunks + small refactor in mkRhsClosure 6a4dc89 Bump Haddock submodule 8265c78 Fix and document Unique generation for sum TyCon and DataCons e710f8f Correct a few mistyped words in prose/comments bbf36f8 More typos in comments fb34b27 Revert "Cleanup PosixSource.h" 86b1522 Unboxed sums: More unit tests bfef2eb StgCmmBind: Some minor simplifications c4f3d91 Add deepseq dependency and a few NFData instances 648fd73 Squash space leaks in the result of byteCodeGen 7f0f1d7 -fprof-auto-top 1fe5c89 UNPACK the size field of SizedSeq d068220 Fix the non-Linux build 4036c1f Testsuite: fix T10482a 1967d74 Some typos in comments a9251c6 MonadUtils: Typos in comments 1783011 Fix productivity calculation (#12424) 9d62f0d Accept better stats for T9675 8f63ba3 Compute boot-defined TyCon names from ModIface. b0a5144 Add mblocks_allocated to GC stats API e98edbd Move stat_startGCSync d3feb16 Make Unique a newtype c06e3f4 Add atomic operations to package.conf.in 89ae1e8 Relevant Bindings no longer reports shadowed bindings (fixes #12176) 750553a Use MO_Cmpxchg in Primops.cmm instead of ccall cas(..) 2078909 Typo in comment 36565a9 ForeignCall.hs: Remove DrIFT directives 55f5aed Track the lengths of the thread queues 988ad8b Fix to thread migration d1fe08e Only trace cap/capset events if we're tracing anything else 4dcbbd1 Remove the DEBUG_ variables, use RtsFlags directly 9df9490 StgSyn: Remove unused StgLiveVars types 2f79e79 Add comment about lexing of INLINE and INLINABLE pragma 0c37aef Update old comment InlinePragma b1e6415 More comments about InlinePragmas 7a06b22 Typo in comment [skip ci] 7a8ef01 Remove `setUnfoldingInfoLazily` a13fda7 Clarify comment on makeCorePair d85b26d CmmLive: Remove some redundant exports 8ecac25 CmmLayoutStack: Minor simplification fc66415 Replace an unsafeCoerce with coerce db5a226 Fix omission in haddock instance head 1101045 Trim all spaces after 'version:' fe4008f Remove identity update of field componentsConfigs f09d654 check that the number of parallel build is greater than 0 e3e2e49 codeGen: Remove binutils<2.17 hack, fixes T11758 ca7e1ad Expanded abbreviations in Haddock documentation ce13a9a Fix an assertion that could randomly fail 89fa4e9 Another try to get thread migration right 8fe1672 Bump `hoopl` submodule, mostly cosmetics 253fc38 Temporarily mark T1969 perf test as broken (#12437) 7354f93 StgCmm: Remove unused Bool field of Return sequel 02614fd Replace some `length . filter` with `count` 9aa5d87 Util.count: Implement as a left-fold instead of a right-fold affcec7 rts/Printer.h: fix constness of argument declaration 03af399 AsmCodeGen: Give linear-scan and coloring reg. allocators different cc names 3bfe6a5 RegAlloc: Remove duplicate seqList (use seqList from Util) bd51064 RegAlloc: Use IntSet/IntMaps instead of generic Set/Maps 7a2e933 Use Data.Functor.Const to implement Data.Data internals 6fe2355 configure.ac: Remove checks for bug 9439 773e3aa T1969: Enable it again but bump the max residency temporarily 4d9c22d Fix typo in Data.Bitraversable Haddocks fe19be2 Cabal submodule update. dd23a4c Actually update haddock.Cabal stats. e79bb2c Fix a bug in unboxed sum layout generation 9684dbb Remove StgRubbishArg and CmmArg ac0e112 Improve missing-sig warning bd0c310 Fix GHCi perf-llvm build on x86_64 37a7bcb Update `nofib` submodule to newest commit 7ad3b49 Misspellings in comments [skip ci] 18f0687 Fix configure detection. ffd4029 fix compilation failure on OpenBSD with system supplied GNU C 4.2.1 fc1432a Update hoopl submodule (extra .gitignore entry) 3551e62 refactor test for __builtin_unreachable into Rts.h macro RTS_UNREACHABLE da99a7f Darwin: Detect broken NM program at configure time f9a11a2 When in sanity mode, un-zero malloc'd memory; fix uninitialized memory bugs. d331ace Minor typofix. b222ef7 Typofix in System.Environment docs. 34da8e5 Typo in comment efc0372 Not-in-scope variables are always errors f352e5c Keep the bindings local during defaultCallStacks 58e7316 Refactor nestImplicTcS d610274 Revert "T1969: Enable it again but bump the max residency temporarily" 113d50b Add gcoerceWith to Data.Type.Coercion b2c5e4c Revert "codeGen: Remove binutils<2.17 hack, fixes T11758" 896d216 Annotate initIfaceCheck with usage information. e907e1f Axe initIfaceTc, tie the knot through HPT (or if_rec_types). 704913c Support for noinline magic function. 1f1bd92 Introduce BootUnfolding, set when unfolding is absent due to hs-boot file. 5a8fa2e When a value Id comes from hi-boot, insert noinline. Fixes #10083. 8fd1848 Retypecheck both before and after finishing hs-boot loops in --make. e528061 We also need to retypecheck before when we do parallel make. 0d3bf62 Fix #12472 by looking for noinline/lazy inside oversaturated applications. f9aa996 pass -z wxneeded or -Wl,-zwxneeded for linking on OpenBSD fb0d87f Splice singleton unboxed tuples correctly with Template Haskell 1f75440 Extra comments, as per SPJ in #12035. acdbd16 Move #12403, #12513 users guide notes to 8.2.1 release notes 89facad Add T12520 as a test 1766bb3 RtClosureInspect: Fix off-by-one error in cvReconstructType 613d745 Template Haskell support for unboxed sums 7a86f58 Comments only: Refer to actually existing Notes 8d92b88 DmdAnal: Add a final, safe iteration d6fd2e3 DmdAnal: Testcase about splitFVs and dmdFix abortion ec7fcfd Degrade "case scrutinee not known to diverge for sure" Lint error to warning faaf313 WwLib: Add strictness signature to "let x = absentError …" 1083f45 Fix doc build inconsistency ae66f35 Allow typed holes to be levity-polymorphic a60ea70 Move import to avoid warning 0050aff Fix scoping of type variables in instances ca8c0e2 Typofix in docs. 983f660 Template Haskell support for TypeApplications 822af41 Fix broken Haddock comment f4384ef Remove unused DerivInst constructor for DerivStuff 21c2ebf Missing stderr for T12531. 9d17560 GhcMake: limit Capability count to CPU count in parallel mode a5d26f2 rts: enable parallel GC scan of large (32M+) allocation area 044e81b OccName: Remove unused DrIFT directive ff1931e TcGenDeriv: Typofix d168c41 Fix and complete runghc documentation 6781f37 Clarify pkg selection when multiple versions are available 83b326c Fix binary-trees regression from unnecessary floating in CorePrep. a25bf26 Tag pointers in interpreted constructors ef784c5 Fix handling of package-db entries in .ghc.environment files, etc. 2ee1db6 Fixes #12504: Double-escape paths used to build call to hsc_line 28b71c5 users_guide: More capabilities than processors considered harmful 0e74925 GHC: Expose installSignalHandlers, withCleanupSession 3005fa5 iserv: Show usage message on argument parse failure d790cb9 Bump the default allocation area size to 1MB d40d6df StgCmmPrim: Add missing MO_WriteBarrier d1f2239 Clarify scope of `getQ`/`putQ` state. 22259c1 testsuite: Failing testcase for #12091 2d22026 ErrUtils: Expose accessors of ErrDoc and ErrMsg a07a3ff A failing testcase for T12485 9306db0 TysWiredIn: Use dataConWorkerUnique instead of incrUnique 9cfef16 Add Read1/Read2 methods defined in terms of ReadPrec 1ad770f Add -flocal-ghci-history flag (#9089). 010b07a PPC NCG: Implement minimal stack frame header. ca6d0eb testsuite: Update bytes allocated of parsing001 75321ff Add -fdefer-out-of-scope-variables flag (#12170). e9b0bf4 Remove redundant-constraints from -Wall (#10635) 043604c RnExpr: Fix ApplicativeDo desugaring with RebindableSyntax dad6a88 LoadIFace: Show known names on inconsistent interface file 3fb8f48 Revert "testsuite: Update bytes allocated of parsing001" a69371c users_guide: Document removal of -Wredundant-constraints from -Wall ad1e072 users_guide: Move addModFinalizer mention to 8.0.2 release notes 1f5d4a3 users_guide: Move -fdefer-out-of-scope-variables note to 8.0.2 relnotes da920f6 users_guide: Move initGhcMonad note to 8.0.2 relnotes a48de37 restore -fmax-worker-args handling (Trac #11565) 1e39c29 Kill vestiages of DEFAULT_TMPDIR 8d35e18 Fix startsVarSym and refactor operator predicates (fixes #4239) b946cf3 Revert "Fix startsVarSym and refactor operator predicates (fixes #4239)" f233f00 Fix startsVarSym and refactor operator predicates (fixes #4239) e5ecb20 Added support for deprecated POSIX functions on Windows. 0cc3931 configure.ac: fix --host= handling 818760d Fix #10923 by fingerprinting optimization level. 36bba47 Typos in notes 33d3527 Protect StablPtr dereference with the StaticPtr table lock. 133a5cc ghc-cabal: accept EXTRA_HC_OPTS make variable f93c363 extend '-fmax-worker-args' limit to specialiser (Trac #11565) ac2ded3 Typo in comment 57aa6bb Fix comment about result f8b139f test #12567: add new testcase with expected plugin behaviour 1805754 accept current (problematic) output cdbb9da cleanup: drop 11 years old performance hack 71dd6e4 Don't ignore addTopDecls in module finalizers. 6ea6242 Turn divInt# and modInt# into bitwise operations when possible 8d00175 Less scary arity mismatch error message when deriving 4ff4929 Make generated Ord instances smaller (per #10858). 34010db Derive the Generic instance in perf/compiler/T5642 05b497e distrib: Fix libdw bindist check a7a960e Make the test for #11108 less fragile dcc4904 Add failing testcase for #12433 feaa31f Remove references to -XRelaxedPolyRec 5eab6a0 Document meaning of order of --package-db flags, fixes #12485. a8238a4 Update unix submodule to latest HEAD. 65d9597 Add hook for creating ghci external interpreter 1b5f920 Make start address of `osReserveHeapMemory` tunable via command line -xb 7b4bb40 Remove -flocal-ghci-history from default flags 710f21c Add platform warning to Foreign.C.Types 158288b Generalise type of mkMatchGroup to unify with mkMatchGroupName 04184a2 Remove uses of mkMatchGroupName 7b7ea8f Fix derived Ix instances for one-constructor GADTs 0e7ccf6 Fix TH ppr output for list comprehensions with only one Stmt 454033b Add hs_try_putmvar() 03541cb Be less picky about reporing inaccessible code 21d0bfe Remove unused exports 35086d4 users_guide: Fix Docbook remnant b451fef users_guide: #8761 is now fixed c6ac1e5 users_guide: TH now partially supports typed holes 6555c6b rts: Disable -hb with multiple capabilities 5eeabe2 Test wibbles for commit 03541cba ec3edd5 Testsuite wibbles, to the same files 505a518 Comments and white space only 8074e03 Comments and white space only 876b00b Comments and white space 86836a2 Fix codegen bug in PIC version of genSwitch (#12433) 9123845 tryGrabCapability should be using TRY_ACQUIRE_LOCK 626db8f Unify CallStack handling in ghc a001299 Comments only a72d798 Comments in TH.Syntax (Trac #12596) 97b47d2 Add test case for #7611 ea310f9 Remove directories from include paths 14c2e8e Codegen for case: Remove redundant void id checks 6886bba Bump Haddock submodule to fix rendering of class methods 8bd3d41 Fix failing test T12504 9cbcdb4 shutdownHaskellAndExit: just do a normal hs_exit() (#5402) 74c4ca0 Expose hs_exit_(rtsFalse) as hs_exit_nowait() 3a17916 Improved documentation for Foreign.Concurrent (#12547) 9766b0c Fix #12442. d122935 Mark mapUnionFV as INLINABLE rather than INLINE 68f72f1 Replace INLINEABLE by INLINABLE (#12613) 55d92cc Update test output bc7c730 Pattern Synonyms documentation update 796f0f2 Print foralls in user format b0ae0dd Remove #ifdef with never fulfilled condition c36904d Fix layout of MultiWayIf expressions (#10807) f897b74 TH: Use atomicModifyIORef' for fresh names 0b6024c Comments and manual only: spelling 13d3b53 Test Trac #12634 f21eedb Check.hs: Use actual import lists instead of comments 0b533a2 A bit of tracing about flattening 2fbfbca Fix desugaring of pattern bindings (again) 66a8c19 Fix a bug in occurs checking 3012c43 Add Outputable Report in TcErrors b612da6 Fix impredicativity (again) fc4ef66 Comments only 5d473cd Add missing stderr file 3f27237 Make tcrun042 fail 28a00ea Correct spelling in note references b3d55e2 Document Safe Haskell restrictions on Generic instances 9e86276 Implement deriving strategies b61b7c2 CodeGen X86: fix unsafe foreign calls wrt inlining 59d7ee5 GHCi: Don't remove shadowed bindings from typechecker scope. 3c17905 Support more than 64 logical processors on Windows 151edd8 Recognise US spelling for specialisation flags. f869b23 Move -dno-debug-output to the end of the test flags d1b4fec Mark T11978a as broken due to #12019 1e795a0 Use check stacking on Windows. c93813d Add NUMA support for Windows 2d6642b Fix interaction of record pattern synonyms and record wildcards 1851349 Don't warn about name shadowing when renaming the patten in a PatSyn decl ce3370e PPC/CodeGen: fix lwa instruction generation 48ff084 Do not warn about unused underscore-prefixed fields (fixes Trac #12609) 0014fa5 ghc-pkg: Allow unregistering multiple packages in one call b0d53a8 Turn `__GLASGOW_HASKELL_LLVM__` into an integer again f547b44 Eliminate some unsafeCoerce#s with deriving strategies 23cf32d Disallow standalone deriving declarations involving unboxed tuples or sums 4d2b15d validate: Add --build-only 42f1d86 runghc: use executeFile to run ghc process on POSIX 3630ad3 Mark #6132 as broken on OS X 8cab9bd Ignore output from derefnull and divbyzero on Darwin e9104d4 DynFlags: Fix absolute import path to generated header eda5a4a testsuite: Mark test for #12355 as unbroken on Darwin. 22c6b7f Update Cabal submodule to latest version. 8952cc3 runghc: Fix import of System.Process on Windows 7a6731c genapply: update source file in autogenerated text c5d6288 Mark zipWithAndUnzipM as INLINABLE rather than INLINE e4cf962 Bring Note in TcDeriv up to date 465c6c5 Improve error handling in TcRnMonad 58ecdf8 Remove unused T12124.srderr 4a03012 Refactor TcDeriv and TcGenDeriv a2bedb5 RegAlloc: Make some pattern matched complete 57a207c Remove dead code “mkHsConApp” cbe11d5 Add compact to packages so it gets cleaned on make clean. e41b9c6 Fix memory leak from #12664 f3be304 Don't suggest deprecated flags in error messages 76aaa6e Simplify implementation of wWarningFlags 082991a Tc267, tests what happens if you forgot to knot-tie. 3b9e45e Note about external interface changes. 940ded8 Remove reexports from ghc-boot, help bootstrap with GHC 8. 887485a Exclude Cabal PackageTests from gen_contents_index. 00b530d The Backpack patch. 4e8a060 Distinguish between UnitId and InstalledUnitId. 5bd8e8d Make InstalledUnitId be ONLY a FastString. 027a086 Update haddock.Cabal perf for Cabal update. 61b143a Report that we support Backpack in --info. 46b78e6 Cabal submodule update. e660f4b Rework renaming of children in export lists. f2d80de Add trailing comma to fix the build. 21647bc Fix build 7b060e1 Generate a unique symbol for signature object stub files, fixes #12673 bcd3445 Do not segfault if no common root can be found 8dc72f3 Cleanup PosixSource.h 6c47f2e Default +RTS -qn to the number of cores 85e81a8 Turn on -n4m with -A16m or greater 1a9705c Escape lambda. b255ae7 Orient improvement constraints better b5c8963 Rename a parameter; trivial refactor 88eb773 Delete orphan where clause 76a5477 Move zonking out of tcFamTyPats cc5ca21 Improved stats for Trac #1969 a6111b8 More tests for Trac #12522 b5be2ec Add test case for #12689 f8d2c20 Add a broken test case for #12689 8fa5f5b Add derived shadows only for Wanted constraints d2959df Comments and equation ordering only bce9908 RnExpr: Actually fail if patterns found in expression 577effd testsuite: Bump T1969 allocations 184d7cb Add test for #12411 042c593 Add test for #12589 fef1df4 Add test for #12456 57f7a37 Add missing @since annotations 2fdf21b Further improve error handling in TcRn monad 015e9e3 Cabal submodule update. 1cccb64 Unique: Simplify encoding of sum uniques 34d933d Clean up handling of known-key Names in interface files 3991da4 MkIface: Turn a foldr into a foldl' aa06883 Improve find_lbl panic message 90df91a PrelInfo: Fix style 8c6a3d6 Add missing Semigroup instances for Monoidal datatypes in base d5a4e49 Make error when deriving an instance for a typeclass less misleading 3ce0e0b Build ghc-iserv with --export-dynamic 6c73932 Check for empty entity string in "prim" foreign imports 0d9524a Disable T-signals-child test on single-threaded runtime e39589e Fix Windows build following D2588 b501709 Fix Show derivation in the presence of RebindableSyntax/OverloadedStrings 512541b Add a forward reference for a Note afdde48 Correct name of makeStableName in haddock 3174beb Comments about -Wredundant-constraints 82b54fc Fix comment typo 692c8df Fix shadowing in mkWwBodies 609d2c8 Typo in comment a693d1c Correct order of existentials in pattern synonyms f7278a9 Fix wrapping order in matchExpectedConTy 1790762 Test Trac #12681 db71d97 Reduce trace output slightly 156db6b Add more variants of T3064 (in comments) a391a38 Comments only f43db14 Typos in comments 3adaacd Re-add accidentally-deleted line 9cb4459 testsuite: Work around #12554 deed418 testsuite: Mark break011 as broken 8b84b4f testsuite: Mark T10858 as broken on Windows 3325435 testsuite: Mark T9405 as broken on Windows 8bb960e testsuite/driver: Never symlink on Windows c6ee773 testsuite/timeout: Ensure that processes are cleaned up on Windows 17d696f validate: Allow user to override Python interpreter 7d2df32 testsuite/driver: More Unicode awareness 5b55e4b testsuite: Eliminate unnecessary compile_timeout_multiplier 2864ad7 testsuite/driver: Allow threading on Windows c5c6d80 testsuite: Mark T7037 as broken on Windows cf5eec3 Bump parallel submodule 8fa2cdb Track dep_finsts in exports hash, as it affects downstream deps. f148513 Add option to not retain CAFs to the linker API 1275994 remove unnecessary ifdef 46f5f02 fixup! Add option to not retain CAFs to the linker API 7129861 DynamicLoading: Replace map + zip with zipWith 161f463 ghc/Main.hs: Add import list to DynamicLoading fa8940e fix build failure on Solaris caused by usage of --export-dynamic a3bc93e Add some missing RTS symbols 3866481 Compute export hash based on ALL transitive orphan modules. 02f2f21 cmm/Hoopl/Dataflow: remove unused code 1f09c16 Test for newtype with unboxed argument 2cb8cc2 StgCmmPrim: Add missing write barrier. a6094fa configure.ac: Report Unregisterised setting 518f289 New story for abstract data types in hsig files. 7e77c4b Support constraint synonym implementations of abstract classes. 9df4ce4 Only delete instances when merging when there is an exact match. 01490b4 Mark previously failing backpack tests as passing, with correct output. c2142ca Fix Mac OS X build by removing space after ASSERT. c23dc61 check-cpp: Make it more robust ff225b4 Typos in comments 45bfd1a Refactor typechecking of pattern bindings 82efad7 Comments and trivial refactoring cdbc73a Test Trac #12507 d61c7e8 Make TcLevel increase by 1 not 2 3f5673f A collection of type-inference refactorings. 1f09b24 Accept 20% dedgradation in Trac #5030 compile time 9417e57 Refactor occurrence-check logic e1fc5a3 Define emitNewWantedEq, and use it 6ddba64 Improve TcCanonical.unifyWanted and unifyDerived f41a8a3 Add and use a new dynamic-library-dirs field in the ghc-pkg info acc9851 Fix failure in setnumcapabilities001 (#12728) 1050e46 rts: configure.ac should populate HAVE_LIBNUMA instead of USE_LIBNUMA a662f46 Skip T5611 on OSX as it fails non-deterministically. 3cb32d8 Add -Wcpp-undef warning flag 6e9a51c Refactoring: Delete copied function in backpack/NameShape b76cf04 cmm/Hoopl/Dataflow: minor cleanup aaede1e rts/package.conf.in: Fix CPP usage a6bcf87 Refactoring: Replace when (not ...) with unless in ErrUtils f084e68 rts: Move path utilities to separate source file 1c4a39d Prioritise class-level equality costraints 1221f81 Don't instantaite when typechecking a pattern synonym 08ba691 Take account of kinds in promoteTcType 03b0b8e Test Trac #12174 853cdae Test Trac #12081 a182c0e testsuite: Bump peak_megabytes_allocated for T3064 801c263 Fundeps work even for unary type classes 9f814b2 Delete extraneous backtick in users' guide 925d178 Make traceRn behave more like traceTc 488a9ed rts/linker: Move loadArchive to new source file 23143f6 Refine ASSERT in buildPatSyn for the nullary case. 48876ae Remove -dtrace-level b8effa7 CmmUtils: remove the last dataflow functions 3562727 Simple refactor to remove misleading comment f9308c2 Collect coercion variables, not type variables eefe86d Allow levity-polymorpic arrows 0eb8934 Fix typo in comment cc29eb5 Revert "rts/linker: Move loadArchive to new source file" 815b837 Minor doc addition as requested in #12774. 7187ded Clarify comments on kinds (Trac #12536) aae2b3d Make it possible to use +RTS -qn without -N 60343a4 Add test for #12732 5ebcb3a Document unpackClosure# primop 4b300a3 Minor refactoring in stg_unpackClosurezh 4e088b4 Fix a bug in parallel GC synchronisation 7ddbdfd Zap redundant imports 80d4a03 Typos in comments 795be0e Align GHCi's library search order more closely with LDs 0b70ec0 Have static pointers work with -fno-full-laziness. 19ce8a5 Sparc*: Prevent GHC from doing unaligned accesses 79fb6e6 Tiny refactor 9968949 Get rid of TcTyVars more assiduously 7a50966 Simplify the API for TcHsType.kcHsTyVarBndrs f4a14d6 Use substTyUnchecked in TcMType.new_meta_tv_x 13508ba Fix Trac #12797: approximateWC 623b8e4 Renaming and comments in CorePrep 8a5960a Uninstall signal handlers cc4710a testsuite: Simplify kernel32 glue logic f4fb3bc linker: Split out CacheFlush logic abfa319 linker: Shuffle configuration into LinkerInternals.h 43c8c1c linker: Move mmapForLinker declaration into LinkerInternals.h 3f05126 linker: Split symbol extras logic into new source file c3446c6 Shuffle declarations into LinkerInternals.h 6ea0b4f linker: Split PEi386 implementation into new source file f6c47df linker: Split MachO implementation into new source file bdc262c linker: Split ELF implementation into separate source file 6fecb7e linker: Move ARM interworking note to SymbolExtras.c dc4d596 Hoopl/Dataflow: make the module more self-contained 80076fa Add notes describing SRT concepts b5460dd Add testcase for #12757 967dd5c Merge cpe_ExprIsTrivial and exprIsTrivial eaa3482 testsuite: Update T10858 allocations ec22bac Add test for #12788 f46bfeb API Annotations: make all ModuleName Located a977c96 Omit unnecessary linker flags e43f05b Add comments from Trac #12768 7b0ae41 Remove a debug trace 2cdd9bd Take account of injectivity when doing fundeps b012120 Handle types w/ type variables in signatures inside patterns (DsMeta) 1cab42d Update release notes for type sigs in TH patterns patch 1c886ea Stop -dno-debug-output suppressing -ddump-tc-trace 25c8e80 Add tracing infrastructure to pattern match checker 630d881 Allow GeneralizedNewtypeDeriving for classes with associated type families ead83db Describe symptoms of (and the cure for) #12768 in 8.0.2 release notes 1964d86 Some minor linker cleanups. 7d988dd Fix broken validate build. 91f9e13 Fix hs_try_putmvar003 (#12800) 2e8463b Update 8.0.2 release notes for #12784 2325afe Fix comment about pointer tagging 7fe7163 Adapt the (commented out) pprTrace in OccurAnal f05d685 Refactoring of mkNewTypeEqn 317236d Refactor CallStack defaulting slightly 500d90d ghc-cabal: Use correct name of linker flags env variable 816d2e4 build system: Include CONF_LD_LINKER_OPTS in ALL_LD_OPTS 9030d8e configure: Pass HC_OPTS_STAGEx to build system bae4a55 Pass -no-pie to GCC 0a122a4 testsuite: Update allocation numbers for T5631 e06e21a Add Richard Eisenberg's new email to mailmap bef7e78 Read parentheses better 122d826 rts: Add api to pin a thread to a numa node but without fixing a capability aa10c67 rts/linker: Move loadArchive to new source file e8ae4dc Update user's guide after D2490 03e8d26 Prevent GND from inferring an instance context for method-less classes 60bb9d1 Revert "Pass -no-pie to GCC" 7a7bb5d Revert "Refactor CallStack defaulting slightly" ec0bf81 rts: Fix LoadArchive on OS X d421a7e Pass -no-pie to GCC 46e2bef testsuite: Lower allocations for T876 7eae862 ghc-pkg: Munge dynamic library directories 2cfbee8 rts: Fix build when linked with gold 4e0b8f4 rts: Fix #include of 587dccc Make default output less verbose (source/object paths) 568e003 template-haskell: Version bump ca1b986 ghc: Fix ghc's template-haskell bound 8cb7bc5 rts: Fix references to UChar 6c0f10f Kill Type pretty-printer 55d535d Remove CONSTR_STATIC 034e01e Accept output for scc003 e0ca7ff Fix numa001 failure with "too many NUMA nodes" cb16890 testsuite: Fix creep of T4029 011af2b configure: Verify that GCC recognizes -no-pie flag 1b336d9 Skip 64-bit symbol tables 98f9759 Hopefully fix build on OS X 642adec Mark T12041 as expect_broken with -DDEBUG (#12826) 017d11e Typos in comments, notes and manual 31d5b6e fixup! Stop the simplifier from removing StaticPtr binds. 0e58652 Test for unnecessary register spills 4a835f0 Update xhtml submodule a637eeb Don't use mmap symbols when !RTS_LINKER_USE_MMAP 0135188 Storage.c: Pass a size to sys_icache_invalidate fa70b1e Fix -fobject-code with -fexternal-interpreter 7acee06 Avoid calling newDynFlags when there are no changes d3542fa Generalise the implicit prelude import 8dfca69 Inline compiler/NOTES into X86/Ppr.hs b769586 Fix windows validate 31398fb Test for type synonym loops on TyCon. 2878604 Correct spelling of command-line option in comment cede770 Correct name of Note in comment 07e40e9 Add Data instance for Const 18eb57b Revert "Add Data instance for Const" 9a4983d Pass autoconf triplets to sub-project configures 20fb781 LLVM generate llvm.expect for conditional branches 4d4f353 testsuite: Rip out hack for #12554 04b024a GHCi: Unconditionally import System.Directory 231a3ae Have reify work for local variables with functional dependencies. 9c39e09 Switch to LLVM version 3.9 94d1221 Add missing SMP symbols to RT linker. d328abc Spelling in comment only 3bd1dd4 Add Data instance for Const 4b72f85 Optimise whole module exports 6ad94d8 Updated code comment regarding EquationInfo. Trac #12856 ea37b83 A few typos in comments 5bce207 testsuite: Add test for #12855 926469f testsuite: Add test for #12024 b98dbdf testsuite: Add (still broken) testcase for #12447 e7ec521 testsuite: Add (still failing) testcase for #12550 ea76a21 add ieee754 next* functions to math_funs 514acfe Implement fine-grained `-Werror=...` facility 4c0dc76 Ignore Hadrian build products. 7e4b611 Make transformers upstream repository location consistent with others 1399c8b ghc/hschooks.c: Fix include path of Rts.h f430253 Allow to unregister threadWaitReadSTM action. 14ac372 Collect wildcards in sum types during renaming (#12711) d081fcf Make quoting and reification return the same types 9a431e5 Make a panic into an ASSERT 0476a64 Fix a bug in mk_superclasses_of f04f118 Comments only in TcType 0123efd Add elemDVarEnv 1eec1f2 Another major constraint-solver refactoring 18d0bdd Allow TyVars in TcTypes 4431e48 Remove redundant kind check 90a65ad Perf improvements in T6048, T10547 e319466 Typos in comments c1b4b76 Fix a name-space problem with promotion f0f4682 Test Trac #12867 83a952d Test Trac #12845 a5a3926 Kill off ifaceTyVarsOfType bc35c3f Use 'v' instead of 'tpl' for template vars edbe831 Use TyVars in a DFunUnfolding 12eff23 Use TyVars in PatSyns 5f349fe Improve pretty-printing of types eb55ec2 Refactor functional dependencies a bit 1bfff60 Fix inference of partial signatures 086b483 A tiny bit more tc tracing f8c966c Be a bit more selective about improvement 6ec2304 Fix an long-standing bug in OccurAnal 5238842 Typos in comments only [ci skip] 605af54 Test Trac #12776 27a6bdf Test Trac #12885 3aa9368 Comments only (related to #12789) abd4a4c Make note of #12881 in 8.0.2 release notes f8c8de8 Zonk the free tvs of a RULE lhs to TyVars e755930 Typos in comments 36e3622 Store string as parsed in SourceText for CImport 1732d7a Define thread primitives if they're supported. 30cecae users_guide: Bring 8.0.2 release notes up-to-date with ghc-8.0 branch f1fc8cb Make diagnostics slightly more colorful 52222f9b Detect color support da5a61e Minor cleanup of foldRegs{Used,Defd} 2d99da0 testsuite: Mention CLEANUP option in README 3ec8563 Replace -fshow-source-paths with -fhide-source-paths c2268ba Refactor Pattern Match Checker to use ListT 6845087 Purge GHC of literate Perl 4d4e7a5 Use newBlockId instead of newLabelC 7753273 AsmCodeGen: Refactor worker in cmmNativeGens 6d5c2e7 NCGMonad: Add MonadUnique NatM instance eaed140 OrdList: Add Foldable, Traversable instances fe3748b testsuite: Bump haddock.compiler allocations 795f8bd hschooks.c: Ensure correct header file is included 6f7ed1e Make globals use sharedCAF 56d7451 Fix type of GarbageCollect declaration 428e152 Use C99's bool 758b81d rts: Add missing #include 23dc6c4 Remove most functions from cmm/BlockId b92f8e3 Added Eq1, Ord1, Read1 and Show1 instances for NonEmpty 679ccd1 Hoopl/Dataflow: use block-oriented interface 0ce59be Fix testsuite threading, timeout, encoding and performance issues on Windows dd9ba50 Update test output for Windows 605bb9b testsuite: Use python3 by default 20c0614 Update Mingw-w64 bindist for Windows ef37580 Fix windows validate. be8a47f Tweaks to grammar and such. 03766cd Rename RuntimeRepPolymorphism to LevityPolymorphism e2330b6 Revert "Make globals use sharedCAF" c2a2911 Revert "Fix windows validate." 6c54fa5 testsuite: Add another testcase for #11821 0200ded Fix typo in functional dependencies doc f48f5a9e Ensure flags destined for ld are properly passed 514c01e Levity polymorphic expressions mustn't be floated-out in let-bindings. a452c6e Make note of #12907 in 8.0.2 release notes 0ac5e0c rts: Fix type of bool literal 7214e92 testsuite: Remove Unicode literals from driver 6576bf8 rts: Ensure we always give MADV_DONTNEED a chance in osDecommitMemory 0f37550 Typos in comments a934e25 testsuite: Actually update haddock.compiler allocations afb9c30 Reshuffle levity polymorphism checks. 089b085 Intermediate state toward new levity polymorphism From git at git.haskell.org Mon Dec 12 13:21:56 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Dec 2016 13:21:56 +0000 (UTC) Subject: [commit: ghc] master: Disable T12903 due to flakiness (6720376) Message-ID: <20161212132156.CC2763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6720376500c33947fe196b68fe54f5e448376c5d/ghc >--------------------------------------------------------------- commit 6720376500c33947fe196b68fe54f5e448376c5d Author: Tamar Christina Date: Mon Dec 12 14:21:27 2016 +0100 Disable T12903 due to flakiness Test seems to randomly fail on harbormaster. Disabling it until it can be fixed. Test Plan: make test TEST=T12903 Reviewers: austin, bgamari, simonmar, mpickering Reviewed By: mpickering Subscribers: mpickering, thomie, qnikst Differential Revision: https://phabricator.haskell.org/D2821 GHC Trac Issues: #12903 >--------------------------------------------------------------- 6720376500c33947fe196b68fe54f5e448376c5d testsuite/tests/rts/all.T | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index 5037c6b..c44ec04 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -375,7 +375,10 @@ test('numa001', [ extra_run_opts('8'), extra_ways(['debug_numa']) ] test('T12497', [ unless(opsys('mingw32'), skip) ], run_command, ['$MAKE -s --no-print-directory T12497']) + +# Test is being skipped on darwin due to it's flakiness. +# See 12956 test('T12903', [when(opsys('mingw32'), skip), - when(opsys('darwin'), expect_broken(12956))], + when(opsys('darwin'), skip)], compile_and_run, ['']) From git at git.haskell.org Mon Dec 12 16:38:58 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Dec 2016 16:38:58 +0000 (UTC) Subject: [commit: ghc] master: Float unboxed expressions by boxing (bc3d37d) Message-ID: <20161212163858.59F783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bc3d37dada357b04fc5a35f740b4fe7e05292b06/ghc >--------------------------------------------------------------- commit bc3d37dada357b04fc5a35f740b4fe7e05292b06 Author: Simon Peyton Jones Date: Fri Dec 9 00:04:00 2016 +0000 Float unboxed expressions by boxing This patch makes GHC's floating more robust, by allowing it to float unboxed expressions of at least some common types. See Note [Floating MFEs of unlifted type] in SetLevels. This was all provoked by Trac #12603 >--------------------------------------------------------------- bc3d37dada357b04fc5a35f740b4fe7e05292b06 compiler/prelude/TysPrim.hs | 12 +- compiler/prelude/TysWiredIn.hs | 28 ++++ compiler/simplCore/SetLevels.hs | 155 ++++++++++++++------- testsuite/tests/simplCore/should_compile/Makefile | 4 + testsuite/tests/simplCore/should_compile/T12603.hs | 45 ++++++ .../tests/simplCore/should_compile/T12603.stdout | 1 + testsuite/tests/simplCore/should_compile/all.T | 4 + 7 files changed, 195 insertions(+), 54 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc bc3d37dada357b04fc5a35f740b4fe7e05292b06 From git at git.haskell.org Mon Dec 12 16:39:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Dec 2016 16:39:01 +0000 (UTC) Subject: [commit: ghc] master: Fix a long-standing bug in CSE (d03dd23) Message-ID: <20161212163901.1F8EB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d03dd23744799f7df1a73df26d7833887d8e97e9/ghc >--------------------------------------------------------------- commit d03dd23744799f7df1a73df26d7833887d8e97e9 Author: Simon Peyton Jones Date: Thu Dec 8 23:59:47 2016 +0000 Fix a long-standing bug in CSE I had the environments wrong so that CSE could mis-clone an expression, if the uniques just happened to be badly arranged. It's hard to trigger the bug, so I can't make a reliable test case. Happily the fix is easy. >--------------------------------------------------------------- d03dd23744799f7df1a73df26d7833887d8e97e9 compiler/simplCore/CSE.hs | 36 +++++++++++++++++++++++------------- 1 file changed, 23 insertions(+), 13 deletions(-) diff --git a/compiler/simplCore/CSE.hs b/compiler/simplCore/CSE.hs index f119f9f..039da8e 100644 --- a/compiler/simplCore/CSE.hs +++ b/compiler/simplCore/CSE.hs @@ -240,26 +240,34 @@ cseProgram binds = snd (mapAccumL cseBind emptyCSEnv binds) cseBind :: CSEnv -> CoreBind -> (CSEnv, CoreBind) cseBind env (NonRec b e) - = (env2, NonRec b'' e') + = (env2, NonRec b2 e2) where - (env1, b') = addBinder env b - (env2, (b'', e')) = cseRhs env1 b b' e + e1 = tryForCSE env e + (env1, b1) = addBinder env b + (env2, (b2, e2)) = addBinding env1 b b1 e1 cseBind env (Rec pairs) = (env2, Rec pairs') where - (env1, bs') = addRecBinders env (map fst pairs) - (env2, pairs') = mapAccumL cse_rhs env1 (bs' `zip` pairs) - cse_rhs env (b', (b,e)) = cseRhs env b b' e - -cseRhs :: CSEnv -> InId -> OutId -> InExpr -> (CSEnv, (OutId, OutExpr)) -cseRhs env in_id out_id rhs + (bndrs, rhss) = unzip pairs + (env1, bndrs1) = addRecBinders env bndrs + rhss1 = map (tryForCSE env1) rhss + -- Process rhss in extended env1 + (env2, pairs') = mapAccumL cse_rhs env1 (zip3 bndrs bndrs1 rhss1) + cse_rhs env (b, b1, e1) = addBinding env b b1 e1 + +addBinding :: CSEnv -- Includes InId->OutId cloning + -> InId + -> OutId -> OutExpr -- Processed binding + -> (CSEnv, (OutId, OutExpr)) -- Final env and binding +-- Extend the CSE env with a mapping [rhs -> out-id] +-- unless we can instead just substitute [in-id -> rhs] +addBinding env in_id out_id rhs' | no_cse = (env, (out_id, rhs')) | ok_to_subst = (extendCSSubst env in_id rhs', (out_id, rhs')) | otherwise = (extendCSEnv env rhs' id_expr', (zapped_id, rhs')) where id_expr' = varToCoreExpr out_id - rhs' = tryForCSE env rhs zapped_id = zapIdUsageInfo out_id -- Putting the Id into the cs_map makes it possible that -- it'll become shared more than it is now, which would @@ -316,15 +324,17 @@ cseExpr env (Case e bndr ty alts) = cseCase env e bndr ty alts cseCase :: CSEnv -> InExpr -> InId -> InType -> [InAlt] -> OutExpr cseCase env scrut bndr ty alts - = Case scrut' bndr3 ty (map cse_alt alts) + = Case scrut2 bndr3 ty (map cse_alt alts) where + scrut1 = tryForCSE env scrut + bndr1 = zapIdOccInfo bndr -- Zapping the OccInfo is needed because the extendCSEnv -- in cse_alt may mean that a dead case binder -- becomes alive, and Lint rejects that (env1, bndr2) = addBinder env bndr1 - (alt_env, (bndr3, scrut')) = cseRhs env1 bndr bndr2 scrut - -- cseRhs: see Note [CSE for case expressions] + (alt_env, (bndr3, scrut2)) = addBinding env1 bndr bndr2 scrut1 + -- addBinding: see Note [CSE for case expressions] con_target :: OutExpr con_target = lookupSubst alt_env bndr From git at git.haskell.org Mon Dec 12 18:51:11 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Dec 2016 18:51:11 +0000 (UTC) Subject: [commit: ghc] master: Add infix flag for class and data declarations (8f6d241) Message-ID: <20161212185111.3E6323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8f6d241a74efa6f6280689a9b14c36c6a9f4c231/ghc >--------------------------------------------------------------- commit 8f6d241a74efa6f6280689a9b14c36c6a9f4c231 Author: Alan Zimmerman Date: Thu Dec 8 10:43:32 2016 +0200 Add infix flag for class and data declarations Summary: At the moment, data and type declarations using infix formatting produce the same AST as those using prefix. So type a ++ b = c and type (++) a b = c cannot be distinguished in the parsed source, without looking at the OccName details of the constructor being defined. Having access to the OccName requires an additional constraint which explodes out over the entire AST because of its recursive definitions. In keeping with moving the parsed source to more directly reflect the source code as parsed, add a specific flag to the declaration to indicate the fixity, as used in a Match now too. Note: this flag is to capture the fixity used for the lexical definition of the type, primarily for use by ppr and ghc-exactprint. Updates haddock submodule. Test Plan: ./validate Reviewers: mpickering, goldfire, bgamari, austin Reviewed By: mpickering Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2828 GHC Trac Issues: #12942 >--------------------------------------------------------------- 8f6d241a74efa6f6280689a9b14c36c6a9f4c231 compiler/basicTypes/BasicTypes.hs | 12 ++- compiler/hsSyn/Convert.hs | 17 +++-- compiler/hsSyn/HsBinds.hs | 34 ++++----- compiler/hsSyn/HsDecls.hs | 144 +++++++++++++++++------------------- compiler/hsSyn/HsExpr.hs | 127 ++++++++++++------------------- compiler/hsSyn/HsExpr.hs-boot | 19 ++--- compiler/hsSyn/HsLit.hs | 5 +- compiler/hsSyn/HsPat.hs | 17 ++--- compiler/hsSyn/HsPat.hs-boot | 4 +- compiler/hsSyn/HsSyn.hs | 5 +- compiler/hsSyn/HsTypes.hs | 67 +++++++---------- compiler/hsSyn/PlaceHolder.hs | 7 -- compiler/main/GHC.hs | 1 + compiler/parser/RdrHsSyn.hs | 64 +++++++++------- compiler/rename/RnBinds.hs | 2 +- compiler/rename/RnSource.hs | 22 +++++- compiler/rename/RnTypes.hs | 2 +- compiler/typecheck/TcAnnotations.hs | 2 +- compiler/typecheck/TcBinds.hs | 2 +- compiler/typecheck/TcEnv.hs | 5 +- compiler/typecheck/TcGenFunctor.hs | 1 + compiler/typecheck/TcMatches.hs | 1 + compiler/typecheck/TcPat.hs | 3 +- compiler/typecheck/TcPatSyn.hs | 9 +-- compiler/utils/BooleanFormula.hs | 7 +- utils/haddock | 2 +- 26 files changed, 271 insertions(+), 310 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8f6d241a74efa6f6280689a9b14c36c6a9f4c231 From git at git.haskell.org Tue Dec 13 07:11:57 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 07:11:57 +0000 (UTC) Subject: [commit: ghc] master: Sanity check if we pick up an hsig file without -instantiated-with. (24f6bec) Message-ID: <20161213071157.DEA1F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/24f6bec94411aa6c39a2c94ce5154ffe96ae330f/ghc >--------------------------------------------------------------- commit 24f6bec94411aa6c39a2c94ce5154ffe96ae330f Author: Edward Z. Yang Date: Thu Dec 8 19:32:37 2016 -0800 Sanity check if we pick up an hsig file without -instantiated-with. Summary: Previously we would just let compilation proceed along until we tried to pull up the Module for the hsig file, and get main:A instead of , and get a mysterious error. Check for this earlier! Fixes #12955. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2815 GHC Trac Issues: #12955 >--------------------------------------------------------------- 24f6bec94411aa6c39a2c94ce5154ffe96ae330f compiler/basicTypes/Module.hs | 15 ++------------- compiler/main/GhcMake.hs | 18 ++++++++++++++++++ testsuite/tests/backpack/reexport/bkpreex02.stderr | 8 ++++---- testsuite/tests/backpack/should_compile/bkp24.stderr | 4 ++-- testsuite/tests/backpack/should_fail/bkpfail14.stderr | 2 +- testsuite/tests/backpack/should_fail/bkpfail15.stderr | 2 +- testsuite/tests/driver/Makefile | 5 +++++ testsuite/tests/driver/T12955.hsig | 1 + testsuite/tests/driver/T12955.stderr | 9 +++++++++ testsuite/tests/driver/all.T | 2 ++ 10 files changed, 45 insertions(+), 21 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 24f6bec94411aa6c39a2c94ce5154ffe96ae330f From git at git.haskell.org Tue Dec 13 19:21:24 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:24 +0000 (UTC) Subject: [commit: packages/haskeline] master: Bump the lower requirement to 7.4.1. (e5ca1c5) Message-ID: <20161213192124.A28DF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/e5ca1c5b2c145ac50bc45da0f40798fa818e0c24 >--------------------------------------------------------------- commit e5ca1c5b2c145ac50bc45da0f40798fa818e0c24 Author: Judah Jacobson Date: Wed Dec 23 22:28:19 2015 -0800 Bump the lower requirement to 7.4.1. This lets us remove all the old code around encodings, and just rely on the "base" package to do that for us. >--------------------------------------------------------------- e5ca1c5b2c145ac50bc45da0f40798fa818e0c24 .travis.yml | 6 - Setup.hs | 97 +----------- System/Console/Haskeline/Backend/Posix/Encoder.hs | 85 ----------- System/Console/Haskeline/Backend/Posix/IConv.hsc | 177 ---------------------- System/Console/Haskeline/History.hs | 18 --- haskeline.cabal | 37 +---- 6 files changed, 7 insertions(+), 413 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e5ca1c5b2c145ac50bc45da0f40798fa818e0c24 From git at git.haskell.org Tue Dec 13 19:21:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:26 +0000 (UTC) Subject: [commit: packages/haskeline] master: Merge branch 'master' into bump-lower-dep (8d0b3f7) Message-ID: <20161213192126.A88DD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/8d0b3f77efce22912806c9da104843ca189a49f3 >--------------------------------------------------------------- commit 8d0b3f77efce22912806c9da104843ca189a49f3 Merge: e5ca1c5 5e53651 Author: Judah Jacobson Date: Wed Dec 23 22:30:16 2015 -0800 Merge branch 'master' into bump-lower-dep >--------------------------------------------------------------- 8d0b3f77efce22912806c9da104843ca189a49f3 .travis.yml | 4 ++++ System/Console/Haskeline/Backend/Win32.hsc | 2 ++ 2 files changed, 6 insertions(+) From git at git.haskell.org Tue Dec 13 19:21:28 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:28 +0000 (UTC) Subject: [commit: packages/haskeline] master: Revert the hack that was specific to ghc-7.2.1. (9673f11) Message-ID: <20161213192128.AE4133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/9673f11d3377aee523c373f3f3bc4933268cc026 >--------------------------------------------------------------- commit 9673f11d3377aee523c373f3f3bc4933268cc026 Author: Judah Jacobson Date: Wed Dec 23 22:31:28 2015 -0800 Revert the hack that was specific to ghc-7.2.1. >--------------------------------------------------------------- 9673f11d3377aee523c373f3f3bc4933268cc026 .travis.yml | 4 ---- 1 file changed, 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index d14919c..f4c0f29 100644 --- a/.travis.yml +++ b/.travis.yml @@ -22,10 +22,6 @@ before_install: install: - cabal --version - echo "$(ghc --version) [$(ghc --print-project-git-commit-id 2> /dev/null || echo '?')]" - - | - if [ "$GHCVER" = "7.2.1" ]; then - sudo /opt/ghc/$GHCVER/bin/ghc-pkg trust base # To avoid a SafeHaskell bug on GHC 7.2.1 - fi - travis_retry cabal update - cabal install --only-dependencies - cabal install "Cabal == $CABALVER.*" # Use the same Cabal version for Setup.hs and cabal-install From git at git.haskell.org Tue Dec 13 19:21:30 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:30 +0000 (UTC) Subject: [commit: packages/haskeline] master: Remove more obsolete #if's (50f640e) Message-ID: <20161213192130.B454B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/50f640e2992d80e43b107f93e51deb87cf80ae6e >--------------------------------------------------------------- commit 50f640e2992d80e43b107f93e51deb87cf80ae6e Author: Judah Jacobson Date: Wed Dec 23 22:42:00 2015 -0800 Remove more obsolete #if's >--------------------------------------------------------------- 50f640e2992d80e43b107f93e51deb87cf80ae6e System/Console/Haskeline/Backend/Posix.hsc | 9 ------ System/Console/Haskeline/Directory.hsc | 50 ------------------------------ System/Console/Haskeline/Term.hs | 4 --- 3 files changed, 63 deletions(-) diff --git a/System/Console/Haskeline/Backend/Posix.hsc b/System/Console/Haskeline/Backend/Posix.hsc index a028629..18c6b20 100644 --- a/System/Console/Haskeline/Backend/Posix.hsc +++ b/System/Console/Haskeline/Backend/Posix.hsc @@ -35,7 +35,6 @@ import System.Console.Haskeline.Prefs import System.Console.Haskeline.Backend.Posix.Encoder -#if __GLASGOW_HASKELL__ >= 611 import GHC.IO.FD (fdFD) import Data.Dynamic (cast) import System.IO.Error @@ -43,10 +42,6 @@ import GHC.IO.Exception import GHC.IO.Handle.Types hiding (getState) import GHC.IO.Handle.Internals import System.Posix.Internals (FD) -#else -import GHC.IOBase(haFD,FD) -import GHC.Handle (withHandle_) -#endif #if defined(USE_TERMIOS_H) || defined(__ANDROID__) #include @@ -81,7 +76,6 @@ ioctlLayout h = allocaBytes (#size struct winsize) $ \ws -> do else return Nothing unsafeHandleToFD :: Handle -> IO FD -#if __GLASGOW_HASKELL__ >= 611 unsafeHandleToFD h = withHandle_ "unsafeHandleToFd" h $ \Handle__{haDevice=dev} -> do case cast dev of @@ -89,9 +83,6 @@ unsafeHandleToFD h = "unsafeHandleToFd" (Just h) Nothing) "handle is not a file descriptor") Just fd -> return (fdFD fd) -#else -unsafeHandleToFD h = withHandle_ "unsafeHandleToFd" h (return . haFD) -#endif envLayout :: IO (Maybe Layout) envLayout = handle (\(_::IOException) -> return Nothing) $ do diff --git a/System/Console/Haskeline/Directory.hsc b/System/Console/Haskeline/Directory.hsc index 9eb0952..36f57fa 100644 --- a/System/Console/Haskeline/Directory.hsc +++ b/System/Console/Haskeline/Directory.hsc @@ -14,9 +14,7 @@ module System.Console.Haskeline.Directory( import Foreign import Foreign.C import System.Win32.Types -#if __GLASGOW_HASKELL__ >= 611 import qualified System.Directory -#endif #include #include @@ -62,59 +60,11 @@ doesDirectoryExist file = do return $ attrs /= (#const INVALID_FILE_ATTRIBUTES) && (attrs .&. (#const FILE_ATTRIBUTE_DIRECTORY)) /= 0 -#if __GLASGOW_HASKELL__ >= 611 getHomeDirectory :: IO FilePath getHomeDirectory = System.Directory.getHomeDirectory -#else -type HRESULT = #type HRESULT - -foreign import WINDOWS_CCONV "SHGetFolderPathW" c_SHGetFolderPath - :: Ptr () -> CInt -> HANDLE -> DWORD -> LPTSTR -> IO HRESULT - -getHomeDirectory :: IO FilePath -getHomeDirectory = allocaBytes ((#const MAX_PATH) * (#size TCHAR)) $ \pathPtr -> do - result <- c_SHGetFolderPath nullPtr (#const CSIDL_PROFILE) nullPtr 0 pathPtr - - if result /= (#const S_OK) - then return "" - else peekCWString pathPtr -#endif #else --- POSIX --- On 7.2.1 and later, getDirectoryContents uses the locale encoding --- But previous version don't, so we need to decode manually. -#if __GLASGOW_HASKELL__ >= 701 import System.Directory -#else -import Data.ByteString.Char8 (pack, unpack) -import qualified System.Directory as D -import Control.Exception -import System.Console.Haskeline.Backend.Posix.IConv - -getDirectoryContents :: FilePath -> IO [FilePath] -getDirectoryContents path = do - codeset <- getCodeset - encoder <- openEncoder codeset - decoder <- openDecoder codeset - dirEnc <- fmap unpack (encoder path) - filesEnc <- handle (\(_::IOException) -> return []) - $ D.getDirectoryContents dirEnc - mapM (decoder . pack) filesEnc - -doesDirectoryExist :: FilePath -> IO Bool -doesDirectoryExist file = do - codeset <- getCodeset - encoder <- openEncoder codeset - encoder file >>= D.doesDirectoryExist . unpack - -getHomeDirectory :: IO FilePath -getHomeDirectory = do - codeset <- getCodeset - decoder <- openDecoder codeset - handle (\(_::IOException) -> return "") - $ D.getHomeDirectory >>= decoder . pack -#endif #endif diff --git a/System/Console/Haskeline/Term.hs b/System/Console/Haskeline/Term.hs index 9689a16..2b9c023 100644 --- a/System/Console/Haskeline/Term.hs +++ b/System/Console/Haskeline/Term.hs @@ -138,13 +138,9 @@ data Layout = Layout {width, height :: Int} -- | Utility function since we're not using the new IO library yet. hWithBinaryMode :: MonadException m => Handle -> m a -> m a -#if __GLASGOW_HASKELL__ >= 611 hWithBinaryMode h = bracket (liftIO $ hGetEncoding h) (maybe (return ()) (liftIO . hSetEncoding h)) . const . (liftIO (hSetBinaryMode h True) >>) -#else -hWithBinaryMode _ = id -#endif -- | Utility function for changing a property of a terminal for the duration of -- a computation. From git at git.haskell.org Tue Dec 13 19:21:32 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:32 +0000 (UTC) Subject: [commit: packages/haskeline] master: Remove "LANGUAGE CPP" from Setup.hs (82b2a66) Message-ID: <20161213192132.BAAE43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/82b2a66135db174be9e05a21a6398a5f95913760 >--------------------------------------------------------------- commit 82b2a66135db174be9e05a21a6398a5f95913760 Author: Judah Jacobson Date: Wed Dec 23 22:42:56 2015 -0800 Remove "LANGUAGE CPP" from Setup.hs >--------------------------------------------------------------- 82b2a66135db174be9e05a21a6398a5f95913760 Setup.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/Setup.hs b/Setup.hs index 5c56112..68ce844 100644 --- a/Setup.hs +++ b/Setup.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} import Distribution.System import Distribution.PackageDescription import Distribution.Simple From git at git.haskell.org Tue Dec 13 19:21:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:34 +0000 (UTC) Subject: [commit: packages/haskeline] master: Clean up now-trivial functions in the Encoder module. (8a1c804) Message-ID: <20161213192134.C18AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/8a1c8041e086e2b49012c318f1a756ae90b4c352 >--------------------------------------------------------------- commit 8a1c8041e086e2b49012c318f1a756ae90b4c352 Author: Judah Jacobson Date: Wed Dec 23 23:20:18 2015 -0800 Clean up now-trivial functions in the Encoder module. >--------------------------------------------------------------- 8a1c8041e086e2b49012c318f1a756ae90b4c352 System/Console/Haskeline/Backend/DumbTerm.hs | 9 ++-- System/Console/Haskeline/Backend/Posix.hsc | 52 ++++++++++-------- System/Console/Haskeline/Backend/Posix/Encoder.hs | 64 ++--------------------- System/Console/Haskeline/Backend/Terminfo.hs | 11 ++-- 4 files changed, 40 insertions(+), 96 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8a1c8041e086e2b49012c318f1a756ae90b4c352 From git at git.haskell.org Tue Dec 13 19:21:36 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:36 +0000 (UTC) Subject: [commit: packages/haskeline] master: Bump the version to 0.7.3.0. (d932f7f) Message-ID: <20161213192136.C82063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/d932f7feb1aa4febc9638fd298fd0f304aa2b853 >--------------------------------------------------------------- commit d932f7feb1aa4febc9638fd298fd0f304aa2b853 Author: Judah Jacobson Date: Wed Dec 23 23:25:49 2015 -0800 Bump the version to 0.7.3.0. >--------------------------------------------------------------- d932f7feb1aa4febc9638fd298fd0f304aa2b853 haskeline.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/haskeline.cabal b/haskeline.cabal index b9d4684..b5478ca 100644 --- a/haskeline.cabal +++ b/haskeline.cabal @@ -1,6 +1,6 @@ Name: haskeline Cabal-Version: >=1.10 -Version: 0.7.2.2 +Version: 0.7.3.0 Category: User Interfaces License: BSD3 License-File: LICENSE From git at git.haskell.org Tue Dec 13 19:21:38 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:38 +0000 (UTC) Subject: [commit: packages/haskeline] master: Adding threadsafe (in terminal-style interaction) ^Cternal print function. (53c735d) Message-ID: <20161213192138.CECF53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/53c735d48d79a703ca3d9faf548f391d03e9b68c >--------------------------------------------------------------- commit 53c735d48d79a703ca3d9faf548f391d03e9b68c Author: Bakhtiyar Neyman Date: Sat Feb 13 22:39:46 2016 -0800 Adding threadsafe (in terminal-style interaction) ^Cternal print function. >--------------------------------------------------------------- 53c735d48d79a703ca3d9faf548f391d03e9b68c System/Console/Haskeline.hs | 11 +++++++++++ System/Console/Haskeline/Backend/Posix.hsc | 23 +++++++++++++++++++++-- System/Console/Haskeline/RunCommand.hs | 8 ++++++++ System/Console/Haskeline/Term.hs | 21 +++++++++++++-------- haskeline.cabal | 2 +- 5 files changed, 54 insertions(+), 11 deletions(-) diff --git a/System/Console/Haskeline.hs b/System/Console/Haskeline.hs index 058ad8b..fe2cf5e 100644 --- a/System/Console/Haskeline.hs +++ b/System/Console/Haskeline.hs @@ -51,6 +51,7 @@ module System.Console.Haskeline( -- $outputfncs outputStr, outputStrLn, + getExternalPrint, -- * Customization -- ** Settings Settings(..), @@ -318,3 +319,13 @@ withInterrupt act = do -- > handleInterrupt f = handle $ \Interrupt -> f handleInterrupt :: MonadException m => m a -> m a -> m a handleInterrupt f = handle $ \Interrupt -> f + +-- | Return a print function, which is thread-safe and preserves prompt in terminal-style interaction. + +getExternalPrint :: MonadException m => InputT m (String -> IO ()) +getExternalPrint = do + rterm <- InputT ask + return $ case termOps rterm of + Right _ -> putStrOut rterm + Left tops -> externalPrint tops + \ No newline at end of file diff --git a/System/Console/Haskeline/Backend/Posix.hsc b/System/Console/Haskeline/Backend/Posix.hsc index a028629..c8d7b14 100644 --- a/System/Console/Haskeline/Backend/Posix.hsc +++ b/System/Console/Haskeline/Backend/Posix.hsc @@ -281,8 +281,7 @@ posixRunTerm hs layoutGetters keys wrapGetEvent evalBackend = do fileRT <- posixFileRunTerm hs (enc,dec) <- newEncoders return fileRT - { closeTerm = closeTerm fileRT - , termOps = Left TermOps + { termOps = Left TermOps { getLayout = tryGetLayouts layoutGetters , withGetEvent = wrapGetEvent . withPosixGetEvent ch hs dec @@ -292,9 +291,29 @@ posixRunTerm hs layoutGetters keys wrapGetEvent evalBackend = do (runPosixT enc hs) (lift . lift) evalBackend + , externalPrint = writeChan ch . ExternalPrint } + , closeTerm = do + -- This hack is needed to grab latest writes from some other thread. + -- Without it, if you are using another thread to process the logging + -- and write on screen via exposed externalPrint, latest writes from + -- this thread are not able to cross the thread boundary in time. + threadDelay 1 + flushEventQueue (putStrOut fileRT) ch + closeTerm fileRT } +flushEventQueue :: (String -> IO ()) -> Chan Event -> IO () +flushEventQueue print' eventChan = loop + where loop = do + flushed <- isEmptyChan eventChan + if flushed then return () else do + event <- readChan eventChan + case event of + ExternalPrint str -> do + print' (str ++ "\n") >> loop + _ -> do loop + type PosixT m = ReaderT Encoder (ReaderT Handles m) runPosixT :: Monad m => Encoder -> Handles -> PosixT m a -> m a diff --git a/System/Console/Haskeline/RunCommand.hs b/System/Console/Haskeline/RunCommand.hs index 33c81dd..45472f6 100644 --- a/System/Console/Haskeline/RunCommand.hs +++ b/System/Console/Haskeline/RunCommand.hs @@ -40,6 +40,9 @@ runCommandLoop' liftE tops prefix initState cmds getEvent = do KeyInput ks -> do bound_ks <- mapM (asks . lookupKeyBinding) ks loopCmd s $ applyKeysToMap (concat bound_ks) next + ExternalPrint str -> do + printPreservingLineChars s str + readMoreKeys s next loopCmd :: LineChars -> CmdM m (a,[Key]) -> n a loopCmd s (GetKey next) = readMoreKeys s next @@ -57,6 +60,11 @@ runCommandLoop' liftE tops prefix initState cmds getEvent = do moveToNextLine s return x +printPreservingLineChars :: Term m => LineChars -> String -> m () +printPreservingLineChars s str = do + clearLine s + printLines . lines $ str + drawLine s drawReposition :: (Term n, MonadState Layout m) => (forall a . m a -> n a) -> TermOps -> LineChars -> n () diff --git a/System/Console/Haskeline/Term.hs b/System/Console/Haskeline/Term.hs index 9689a16..0e60278 100644 --- a/System/Console/Haskeline/Term.hs +++ b/System/Console/Haskeline/Term.hs @@ -38,12 +38,13 @@ data RunTerm = RunTerm { } -- | Operations needed for terminal-style interaction. -data TermOps = TermOps { - getLayout :: IO Layout - , withGetEvent :: forall m a . CommandMonad m => (m Event -> m a) -> m a - , evalTerm :: forall m . CommandMonad m => EvalTerm m - , saveUnusedKeys :: [Key] -> IO () - } +data TermOps = TermOps + { getLayout :: IO Layout + , withGetEvent :: forall m a . CommandMonad m => (m Event -> m a) -> m a + , evalTerm :: forall m . CommandMonad m => EvalTerm m + , saveUnusedKeys :: [Key] -> IO () + , externalPrint :: String -> IO () + } -- | Operations needed for file-style interaction. -- @@ -96,8 +97,12 @@ matchInit :: Eq a => [a] -> [a] -> ([a],[a]) matchInit (x:xs) (y:ys) | x == y = matchInit xs ys matchInit xs ys = (xs,ys) -data Event = WindowResize | KeyInput [Key] | ErrorEvent SomeException - deriving Show +data Event + = WindowResize + | KeyInput [Key] + | ErrorEvent SomeException + | ExternalPrint String + deriving Show keyEventLoop :: IO [Event] -> Chan Event -> IO Event keyEventLoop readEvents eventChan = do diff --git a/haskeline.cabal b/haskeline.cabal index 7402b6d..a5fc2bc 100644 --- a/haskeline.cabal +++ b/haskeline.cabal @@ -1,6 +1,6 @@ Name: haskeline Cabal-Version: >=1.10 -Version: 0.7.2.2 +Version: 0.7.2.3 Category: User Interfaces License: BSD3 License-File: LICENSE From git at git.haskell.org Tue Dec 13 19:21:40 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:40 +0000 (UTC) Subject: [commit: packages/haskeline] master: Extending concurrent print function to Win32 backend. (0640f91) Message-ID: <20161213192140.D44C73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/0640f9125741368505ad58ec224d3fdc9a55d266 >--------------------------------------------------------------- commit 0640f9125741368505ad58ec224d3fdc9a55d266 Author: Bakhtiyar Neyman Date: Mon Feb 15 21:57:58 2016 -0800 Extending concurrent print function to Win32 backend. >--------------------------------------------------------------- 0640f9125741368505ad58ec224d3fdc9a55d266 System/Console/Haskeline/Backend/Posix.hsc | 18 +----------------- System/Console/Haskeline/Backend/Win32.hsc | 26 ++++++++++++++------------ System/Console/Haskeline/Term.hs | 18 +++++++++++++++++- 3 files changed, 32 insertions(+), 30 deletions(-) diff --git a/System/Console/Haskeline/Backend/Posix.hsc b/System/Console/Haskeline/Backend/Posix.hsc index c8d7b14..11cbe2c 100644 --- a/System/Console/Haskeline/Backend/Posix.hsc +++ b/System/Console/Haskeline/Backend/Posix.hsc @@ -294,26 +294,10 @@ posixRunTerm hs layoutGetters keys wrapGetEvent evalBackend = do , externalPrint = writeChan ch . ExternalPrint } , closeTerm = do - -- This hack is needed to grab latest writes from some other thread. - -- Without it, if you are using another thread to process the logging - -- and write on screen via exposed externalPrint, latest writes from - -- this thread are not able to cross the thread boundary in time. - threadDelay 1 flushEventQueue (putStrOut fileRT) ch - closeTerm fileRT + closeHandles hs } -flushEventQueue :: (String -> IO ()) -> Chan Event -> IO () -flushEventQueue print' eventChan = loop - where loop = do - flushed <- isEmptyChan eventChan - if flushed then return () else do - event <- readChan eventChan - case event of - ExternalPrint str -> do - print' (str ++ "\n") >> loop - _ -> do loop - type PosixT m = ReaderT Encoder (ReaderT Handles m) runPosixT :: Monad m => Encoder -> Handles -> PosixT m a -> m a diff --git a/System/Console/Haskeline/Backend/Win32.hsc b/System/Console/Haskeline/Backend/Win32.hsc index d9c0934..95a7b5b 100644 --- a/System/Console/Haskeline/Backend/Win32.hsc +++ b/System/Console/Haskeline/Backend/Win32.hsc @@ -380,17 +380,20 @@ win32Term = do hs <- consoleHandles ch <- liftIO newChan fileRT <- liftIO $ fileRunTerm stdin - return fileRT { - termOps = Left TermOps { - getLayout = getBufferSize (hOut hs) - , withGetEvent = withWindowMode hs - . win32WithEvent hs ch - , saveUnusedKeys = saveKeys ch - , evalTerm = EvalTerm (runReaderT' hs . runDraw) - (Draw . lift) - }, - closeTerm = closeHandles hs - } + return fileRT + { termOps = Left TermOps { + getLayout = getBufferSize (hOut hs) + , withGetEvent = withWindowMode hs + . win32WithEvent hs ch + , saveUnusedKeys = saveKeys ch + , evalTerm = EvalTerm (runReaderT' hs . runDraw) + (Draw . lift) + , externalPrint = writeChan ch . ExternalPrint + } + , closeTerm = do + flushEventQueue (putStrOut fileRT) ch + closeHandles hs + } win32WithEvent :: MonadException m => Handles -> Chan Event -> (m Event -> m a) -> m a @@ -545,4 +548,3 @@ clearScreen = do liftIO $ fillConsoleChar h ' ' windowSize origin liftIO $ fillConsoleAttribute h attr windowSize origin setPos origin - diff --git a/System/Console/Haskeline/Term.hs b/System/Console/Haskeline/Term.hs index 0e60278..5186a12 100644 --- a/System/Console/Haskeline/Term.hs +++ b/System/Console/Haskeline/Term.hs @@ -46,6 +46,23 @@ data TermOps = TermOps , externalPrint :: String -> IO () } +-- This hack is needed to grab latest writes from some other thread. +-- Without it, if you are using another thread to process the logging +-- and write on screen via exposed externalPrint, latest writes from +-- this thread are not able to cross the thread boundary in time. +flushEventQueue :: (String -> IO ()) -> Chan Event -> IO () +flushEventQueue print' eventChan = yield >> loopUntilFlushed + where loopUntilFlushed = do + flushed <- isEmptyChan eventChan + if flushed then return () else do + event <- readChan eventChan + case event of + ExternalPrint str -> do + print' (str ++ "\n") >> loopUntilFlushed + ErrorEvent e -> throwIO e + -- We don't want to raise exceptions when doing cleanup. + _ -> do loopUntilFlushed + -- | Operations needed for file-style interaction. -- -- Backends can assume that getLocaleLine, getLocaleChar and maybeReadNewline @@ -200,4 +217,3 @@ hGetLocaleLine = guardedEOF $ \h -> do liftIO $ if buff == NoBuffering then fmap BC.pack $ System.IO.hGetLine h else BC.hGetLine h - From git at git.haskell.org Tue Dec 13 19:21:42 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:42 +0000 (UTC) Subject: [commit: packages/haskeline] master: Fixing a trivial bug and a comment. (7502ca2) Message-ID: <20161213192142.DA2573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/7502ca2f91f3e738913ef15c7c167907522a2962 >--------------------------------------------------------------- commit 7502ca2f91f3e738913ef15c7c167907522a2962 Author: Bakhtiyar Neyman Date: Mon Feb 15 23:06:49 2016 -0800 Fixing a trivial bug and a comment. >--------------------------------------------------------------- 7502ca2f91f3e738913ef15c7c167907522a2962 System/Console/Haskeline.hs | 6 +++--- System/Console/Haskeline/Backend/Posix.hsc | 2 +- haskeline.cabal | 2 +- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/System/Console/Haskeline.hs b/System/Console/Haskeline.hs index fe2cf5e..b4fff00 100644 --- a/System/Console/Haskeline.hs +++ b/System/Console/Haskeline.hs @@ -320,12 +320,12 @@ withInterrupt act = do handleInterrupt :: MonadException m => m a -> m a -> m a handleInterrupt f = handle $ \Interrupt -> f --- | Return a print function, which is thread-safe and preserves prompt in terminal-style interaction. - +{- | Return a printing function, which in terminal-style interactions is +thread-safe and may be run concurrently with user input without affecting the +prompt. -} getExternalPrint :: MonadException m => InputT m (String -> IO ()) getExternalPrint = do rterm <- InputT ask return $ case termOps rterm of Right _ -> putStrOut rterm Left tops -> externalPrint tops - \ No newline at end of file diff --git a/System/Console/Haskeline/Backend/Posix.hsc b/System/Console/Haskeline/Backend/Posix.hsc index 11cbe2c..c83d28b 100644 --- a/System/Console/Haskeline/Backend/Posix.hsc +++ b/System/Console/Haskeline/Backend/Posix.hsc @@ -295,7 +295,7 @@ posixRunTerm hs layoutGetters keys wrapGetEvent evalBackend = do } , closeTerm = do flushEventQueue (putStrOut fileRT) ch - closeHandles hs + closeTerm fileRT } type PosixT m = ReaderT Encoder (ReaderT Handles m) diff --git a/haskeline.cabal b/haskeline.cabal index a5fc2bc..c754604 100644 --- a/haskeline.cabal +++ b/haskeline.cabal @@ -1,6 +1,6 @@ Name: haskeline Cabal-Version: >=1.10 -Version: 0.7.2.3 +Version: 0.7.2.2 Category: User Interfaces License: BSD3 License-File: LICENSE From git at git.haskell.org Tue Dec 13 19:21:44 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:44 +0000 (UTC) Subject: [commit: packages/haskeline] master: Point to github wiki (a89ecc1) Message-ID: <20161213192144.DFCB63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/a89ecc15d90c11652d1ce30b70e87ad9a06f0f3a >--------------------------------------------------------------- commit a89ecc15d90c11652d1ce30b70e87ad9a06f0f3a Author: Judah Jacobson Date: Sun Mar 6 12:36:53 2016 -0800 Point to github wiki >--------------------------------------------------------------- a89ecc15d90c11652d1ce30b70e87ad9a06f0f3a README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 2159507..17763e3 100644 --- a/README.md +++ b/README.md @@ -12,7 +12,7 @@ The most recent development source code can be downloaded with: git clone https://github.com/judah/haskeline Further documentation is also available at -[http://trac.haskell.org/haskeline/wiki/WikiDocumentation](http://trac.haskell.org/haskeline/wiki/WikiDocumentation) +[[https://github.com/judah/haskeline/wiki]]. ##Features: From git at git.haskell.org Tue Dec 13 19:21:46 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:46 +0000 (UTC) Subject: [commit: packages/haskeline] master: Fixing a copy-pasting artifact. (67488a5) Message-ID: <20161213192146.E5D353A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/67488a531839db94c7485140f3c1f106b29cd66a >--------------------------------------------------------------- commit 67488a531839db94c7485140f3c1f106b29cd66a Author: Bakhtiyar Neyman Date: Mon Mar 7 01:27:20 2016 -0800 Fixing a copy-pasting artifact. >--------------------------------------------------------------- 67488a531839db94c7485140f3c1f106b29cd66a System/Console/Haskeline/Term.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/System/Console/Haskeline/Term.hs b/System/Console/Haskeline/Term.hs index 5186a12..dfb9ad2 100644 --- a/System/Console/Haskeline/Term.hs +++ b/System/Console/Haskeline/Term.hs @@ -59,9 +59,8 @@ flushEventQueue print' eventChan = yield >> loopUntilFlushed case event of ExternalPrint str -> do print' (str ++ "\n") >> loopUntilFlushed - ErrorEvent e -> throwIO e -- We don't want to raise exceptions when doing cleanup. - _ -> do loopUntilFlushed + _ -> loopUntilFlushed -- | Operations needed for file-style interaction. -- From git at git.haskell.org Tue Dec 13 19:21:48 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:48 +0000 (UTC) Subject: [commit: packages/haskeline] master: Merge pull request #37 from niobium0/external_print (cb1a30c) Message-ID: <20161213192148.EB7293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/cb1a30ca974b2daed45b64afc2127e5893428b25 >--------------------------------------------------------------- commit cb1a30ca974b2daed45b64afc2127e5893428b25 Merge: 5e53651 67488a5 Author: Judah Jacobson Date: Mon Mar 7 16:03:54 2016 -0800 Merge pull request #37 from niobium0/external_print Adding threadsafe (in terminal-style interaction) external print function. >--------------------------------------------------------------- cb1a30ca974b2daed45b64afc2127e5893428b25 System/Console/Haskeline.hs | 11 +++++++++ System/Console/Haskeline/Backend/Posix.hsc | 7 ++++-- System/Console/Haskeline/Backend/Win32.hsc | 26 ++++++++++---------- System/Console/Haskeline/RunCommand.hs | 8 +++++++ System/Console/Haskeline/Term.hs | 38 +++++++++++++++++++++++------- haskeline.cabal | 0 6 files changed, 67 insertions(+), 23 deletions(-) From git at git.haskell.org Tue Dec 13 19:21:50 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:50 +0000 (UTC) Subject: [commit: packages/haskeline] master: Fix the behavior of unix-word-rubout (C-w) for emacs bindings (0a5c8b0) Message-ID: <20161213192150.F0F313A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/0a5c8b05104ce109508bd24f733440a674fb8840 >--------------------------------------------------------------- commit 0a5c8b05104ce109508bd24f733440a674fb8840 Author: Zejun Wu Date: Thu Mar 10 18:00:18 2016 -0800 Fix the behavior of unix-word-rubout (C-w) for emacs bindings >--------------------------------------------------------------- 0a5c8b05104ce109508bd24f733440a674fb8840 System/Console/Haskeline/Emacs.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Console/Haskeline/Emacs.hs b/System/Console/Haskeline/Emacs.hs index d5e0622..66d3297 100644 --- a/System/Console/Haskeline/Emacs.hs +++ b/System/Console/Haskeline/Emacs.hs @@ -89,7 +89,7 @@ rotatePaste im = get >>= loop wordRight, wordLeft, bigWordLeft :: InsertMode -> InsertMode wordRight = goRightUntil (atStart (not . isAlphaNum)) wordLeft = goLeftUntil (atStart isAlphaNum) -bigWordLeft = goLeftUntil (atStart isSpace) +bigWordLeft = goLeftUntil (atStart (not . isSpace)) modifyWord :: ([Grapheme] -> [Grapheme]) -> InsertMode -> InsertMode modifyWord f im = IMode (reverse (f ys1) ++ xs) ys2 From git at git.haskell.org Tue Dec 13 19:21:53 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:53 +0000 (UTC) Subject: [commit: packages/haskeline] master: Merge pull request #39 from watashi/unix_word_rubout (e1a5161) Message-ID: <20161213192153.042F33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/e1a516119ce58dfabe05a2c01b34044523152011 >--------------------------------------------------------------- commit e1a516119ce58dfabe05a2c01b34044523152011 Merge: cb1a30c 0a5c8b0 Author: Judah Jacobson Date: Sat Mar 19 14:00:33 2016 -0700 Merge pull request #39 from watashi/unix_word_rubout Fix the behavior of unix-word-rubout (C-w) for emacs bindings >--------------------------------------------------------------- e1a516119ce58dfabe05a2c01b34044523152011 System/Console/Haskeline/Emacs.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Tue Dec 13 19:21:55 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:55 +0000 (UTC) Subject: [commit: packages/haskeline] master: Merge branch 'issue-reporter' (cec24a1) Message-ID: <20161213192155.0A4273A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/cec24a1ab3481ec946b2fc4f89fb381860cac42b >--------------------------------------------------------------- commit cec24a1ab3481ec946b2fc4f89fb381860cac42b Merge: e1a5161 c5915d2 Author: Judah Jacobson Date: Sun Apr 17 11:19:01 2016 -0700 Merge branch 'issue-reporter' >--------------------------------------------------------------- cec24a1ab3481ec946b2fc4f89fb381860cac42b README.md | 2 +- haskeline.cabal | 3 ++- 2 files changed, 3 insertions(+), 2 deletions(-) From git at git.haskell.org Tue Dec 13 19:21:57 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:57 +0000 (UTC) Subject: [commit: packages/haskeline] master: Merge branch 'master' into bump-lower-dep (3600181) Message-ID: <20161213192157.10B5F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/3600181d0a5f10a8cfc64155f5b5ae86aa769cd9 >--------------------------------------------------------------- commit 3600181d0a5f10a8cfc64155f5b5ae86aa769cd9 Merge: a89ecc1 cec24a1 Author: Judah Jacobson Date: Sun Apr 24 09:50:02 2016 -0700 Merge branch 'master' into bump-lower-dep Conflicts: README.md System/Console/Haskeline/Backend/Posix.hsc haskeline.cabal >--------------------------------------------------------------- 3600181d0a5f10a8cfc64155f5b5ae86aa769cd9 README.md | 2 +- System/Console/Haskeline.hs | 11 +++++++++ System/Console/Haskeline/Backend/Posix.hsc | 11 +++++---- System/Console/Haskeline/Backend/Win32.hsc | 26 ++++++++++---------- System/Console/Haskeline/Emacs.hs | 2 +- System/Console/Haskeline/RunCommand.hs | 8 +++++++ System/Console/Haskeline/Term.hs | 38 +++++++++++++++++++++++------- haskeline.cabal | 1 + 8 files changed, 72 insertions(+), 27 deletions(-) diff --cc System/Console/Haskeline/Backend/Posix.hsc index 0271a7f,c83d28b..865c095 --- a/System/Console/Haskeline/Backend/Posix.hsc +++ b/System/Console/Haskeline/Backend/Posix.hsc @@@ -284,23 -279,29 +284,26 @@@ posixRunTerm : posixRunTerm hs layoutGetters keys wrapGetEvent evalBackend = do ch <- newChan fileRT <- posixFileRunTerm hs - (enc,dec) <- newEncoders return fileRT - { closeTerm = closeTerm fileRT - , termOps = Left TermOps + { termOps = Left TermOps { getLayout = tryGetLayouts layoutGetters , withGetEvent = wrapGetEvent - . withPosixGetEvent ch hs dec + . withPosixGetEvent ch hs keys , saveUnusedKeys = saveKeys ch - , evalTerm = - mapEvalTerm (runPosixT hs) lift evalBackend + , evalTerm = mapEvalTerm - (runPosixT enc hs) - (lift . lift) - evalBackend ++ (runPosixT hs) lift evalBackend + , externalPrint = writeChan ch . ExternalPrint } + , closeTerm = do + flushEventQueue (putStrOut fileRT) ch + closeTerm fileRT } -type PosixT m = ReaderT Encoder (ReaderT Handles m) +type PosixT m = ReaderT Handles m -runPosixT :: Monad m => Encoder -> Handles -> PosixT m a -> m a -runPosixT enc h = runReaderT' h . runReaderT' enc +runPosixT :: Monad m => Handles -> PosixT m a -> m a +runPosixT h = runReaderT' h fileRunTerm :: Handle -> IO RunTerm fileRunTerm h_in = posixFileRunTerm Handles diff --cc haskeline.cabal index b5478ca,ea41164..af32974 --- a/haskeline.cabal +++ b/haskeline.cabal @@@ -16,8 -16,9 +16,9 @@@ Description Haskell programs. . Haskeline runs both on POSIX-compatible systems and on Windows. -Homepage: https://github.com/judah/haskeline +Homepage: http://trac.haskell.org/haskeline + Bug-Reports: https://github.com/judah/haskeline/issues -Stability: Experimental +Stability: Stable Build-Type: Custom extra-source-files: examples/Test.hs Changelog From git at git.haskell.org Tue Dec 13 19:21:59 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:21:59 +0000 (UTC) Subject: [commit: packages/haskeline] master: Merge branch 'release-0.7.2.3' (80bfa5d) Message-ID: <20161213192159.167783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/80bfa5d3ced4c8c4de701daefeafb96a405f0eb8 >--------------------------------------------------------------- commit 80bfa5d3ced4c8c4de701daefeafb96a405f0eb8 Merge: 3600181 8addaa2 Author: Judah Jacobson Date: Sun Apr 24 12:22:44 2016 -0700 Merge branch 'release-0.7.2.3' Conflicts: haskeline.cabal >--------------------------------------------------------------- 80bfa5d3ced4c8c4de701daefeafb96a405f0eb8 Changelog | 5 +++++ 1 file changed, 5 insertions(+) From git at git.haskell.org Tue Dec 13 19:22:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:22:01 +0000 (UTC) Subject: [commit: packages/haskeline] master: Add Changelog for 0.7.3.0. (3cf1bd3) Message-ID: <20161213192201.1CA8B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/3cf1bd3df37e1069f93c05d379f60b296c15618e >--------------------------------------------------------------- commit 3cf1bd3df37e1069f93c05d379f60b296c15618e Author: Judah Jacobson Date: Sun Apr 24 12:26:13 2016 -0700 Add Changelog for 0.7.3.0. >--------------------------------------------------------------- 3cf1bd3df37e1069f93c05d379f60b296c15618e Changelog | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/Changelog b/Changelog index 7b1f5e2..1ff7b9b 100644 --- a/Changelog +++ b/Changelog @@ -1,3 +1,7 @@ +Changed in version 0.7.3.0: + * Require ghc version of at least 7.4.1, and clean up obsolete code + * Add thread-safe (in terminal-style interaction) external print function + Changed in version 0.7.2.3: * Fix hsc2hs-related warning on ghc-8 * Fix the behavior of ctrl-W in the emacs bindings From git at git.haskell.org Tue Dec 13 19:22:03 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:22:03 +0000 (UTC) Subject: [commit: packages/haskeline] master: Fix withInterrupt function docs (df94abf) Message-ID: <20161213192203.21D5B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/df94abfa2ea8a9d6fa5a913467111213467beaca >--------------------------------------------------------------- commit df94abfa2ea8a9d6fa5a913467111213467beaca Author: Roman Zaynetdinov Date: Sat Jun 4 13:08:05 2016 +0300 Fix withInterrupt function docs Change outdated (I suppose so) `wrapInterrupt` to actual `withInterrupt`. >--------------------------------------------------------------- df94abfa2ea8a9d6fa5a913467111213467beaca System/Console/Haskeline.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/System/Console/Haskeline.hs b/System/Console/Haskeline.hs index b4fff00..0eea273 100644 --- a/System/Console/Haskeline.hs +++ b/System/Console/Haskeline.hs @@ -294,13 +294,13 @@ of type 'Interrupt'. For example: > tryAction :: InputT IO () > tryAction = handle (\Interrupt -> outputStrLn "Cancelled.") -> $ wrapInterrupt $ someLongAction +> $ withInterrupt $ someLongAction The action can handle the interrupt itself; a new 'Interrupt' exception will be thrown every time Ctrl-C is pressed. > tryAction :: InputT IO () -> tryAction = wrapInterrupt loop +> tryAction = withInterrupt loop > where loop = handle (\Interrupt -> outputStrLn "Cancelled; try again." >> loop) > someLongAction From git at git.haskell.org Tue Dec 13 19:22:05 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:22:05 +0000 (UTC) Subject: [commit: packages/haskeline] master: Merge pull request #41 from zaynetro/patch-1 (f18a911) Message-ID: <20161213192205.2737F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/f18a911bd8399904475036253c7864cb301061f7 >--------------------------------------------------------------- commit f18a911bd8399904475036253c7864cb301061f7 Merge: 3cf1bd3 df94abf Author: Judah Jacobson Date: Sat Jun 4 08:48:17 2016 -0700 Merge pull request #41 from zaynetro/patch-1 Fix withInterrupt function docs >--------------------------------------------------------------- f18a911bd8399904475036253c7864cb301061f7 System/Console/Haskeline.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) From git at git.haskell.org Tue Dec 13 19:22:07 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:22:07 +0000 (UTC) Subject: [commit: packages/haskeline] master: MonadFix instance for InputT (13d2bd1) Message-ID: <20161213192207.2C7063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/13d2bd1d4bd02a89026f26ec02510e40b872ce34 >--------------------------------------------------------------- commit 13d2bd1d4bd02a89026f26ec02510e40b872ce34 Author: Alexander Vieth Date: Tue Jun 21 18:16:37 2016 -0400 MonadFix instance for InputT >--------------------------------------------------------------- 13d2bd1d4bd02a89026f26ec02510e40b872ce34 System/Console/Haskeline/InputT.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/System/Console/Haskeline/InputT.hs b/System/Console/Haskeline/InputT.hs index c1ee55e..1fcd4cc 100644 --- a/System/Console/Haskeline/InputT.hs +++ b/System/Console/Haskeline/InputT.hs @@ -15,6 +15,7 @@ import System.Directory(getHomeDirectory) import System.FilePath import Control.Applicative import Control.Monad (liftM, ap) +import Control.Monad.Fix import System.IO import Data.IORef @@ -56,6 +57,9 @@ newtype InputT m a = InputT {unInputT :: instance MonadTrans InputT where lift = InputT . lift . lift . lift . lift . lift +instance ( MonadFix m ) => MonadFix (InputT m) where + mfix f = InputT (mfix (unInputT . f)) + -- | Get the current line input history. getHistory :: MonadIO m => InputT m History getHistory = InputT get From git at git.haskell.org Tue Dec 13 19:22:09 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:22:09 +0000 (UTC) Subject: [commit: packages/haskeline] master: Merge pull request #42 from avieth/aovieth/monad_fix (c0e985e) Message-ID: <20161213192209.31E853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/c0e985e58e9e75e4cd99cb75f8ab703ad1afd5c5 >--------------------------------------------------------------- commit c0e985e58e9e75e4cd99cb75f8ab703ad1afd5c5 Merge: f18a911 13d2bd1 Author: Judah Jacobson Date: Wed Sep 7 09:14:03 2016 -0700 Merge pull request #42 from avieth/aovieth/monad_fix MonadFix instance for InputT >--------------------------------------------------------------- c0e985e58e9e75e4cd99cb75f8ab703ad1afd5c5 System/Console/Haskeline/InputT.hs | 4 ++++ 1 file changed, 4 insertions(+) From git at git.haskell.org Tue Dec 13 19:22:11 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:22:11 +0000 (UTC) Subject: [commit: packages/haskeline] master: .travis.yml: Add ghc 7.10.3 and 8.0.1 (08e972b) Message-ID: <20161213192211.372DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/08e972b6492a5db240f2b6bcf57417f0b5862bab >--------------------------------------------------------------- commit 08e972b6492a5db240f2b6bcf57417f0b5862bab Author: Erik de Castro Lopo Date: Wed Sep 7 20:46:05 2016 +1000 .travis.yml: Add ghc 7.10.3 and 8.0.1 >--------------------------------------------------------------- 08e972b6492a5db240f2b6bcf57417f0b5862bab .travis.yml | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index f4c0f29..775d0b0 100644 --- a/.travis.yml +++ b/.travis.yml @@ -10,7 +10,9 @@ env: - CABALVER=1.18 GHCVER=7.8.1 - CABALVER=1.18 GHCVER=7.8.2 - CABALVER=1.18 GHCVER=7.8.3 - - CABALVER=1.22 GHCVER=7.10.1 + - CABALVER=1.18 GHCVER=7.8.4 + - CABALVER=1.22 GHCVER=7.10.3 + - CABALVER=1.24 GHCVER=8.0.1 # Note: the distinction between `before_install` and `install` is not important. before_install: From git at git.haskell.org Tue Dec 13 19:22:13 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:22:13 +0000 (UTC) Subject: [commit: packages/haskeline] master: Merge pull request #43 from erikd/master (7ac8df7) Message-ID: <20161213192213.3D4C63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/7ac8df7fc8fbd76918f7d52dff8b16f008a20f98 >--------------------------------------------------------------- commit 7ac8df7fc8fbd76918f7d52dff8b16f008a20f98 Merge: c0e985e 08e972b Author: Judah Jacobson Date: Tue Sep 20 09:32:57 2016 -0700 Merge pull request #43 from erikd/master .travis.yml: Add ghc 8.0.1 >--------------------------------------------------------------- 7ac8df7fc8fbd76918f7d52dff8b16f008a20f98 .travis.yml | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) From git at git.haskell.org Tue Dec 13 19:22:15 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:22:15 +0000 (UTC) Subject: [commit: packages/haskeline] master: Bump upper bound on base (db4413d) Message-ID: <20161213192215.42C973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/db4413d49b836c7cdfade489fd504e559bb2ba71 >--------------------------------------------------------------- commit db4413d49b836c7cdfade489fd504e559bb2ba71 Author: Ben Gamari Date: Tue Nov 15 14:35:44 2016 -0500 Bump upper bound on base >--------------------------------------------------------------- db4413d49b836c7cdfade489fd504e559bb2ba71 haskeline.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/haskeline.cabal b/haskeline.cabal index af32974..1a9b86e 100644 --- a/haskeline.cabal +++ b/haskeline.cabal @@ -42,7 +42,7 @@ Library -- We require ghc>=7.4.1 (base>=4.5) to use the base library encodings, even -- though it was implemented in earlier releases, due to GHC bug #5436 which -- wasn't fixed until 7.4.1 - Build-depends: base >=4.5 && < 4.10, containers>=0.4 && < 0.6, + Build-depends: base >=4.5 && < 4.11, containers>=0.4 && < 0.6, directory>=1.1 && < 1.3, bytestring>=0.9 && < 0.11, filepath >= 1.2 && < 1.5, transformers >= 0.2 && < 0.6 Default-Language: Haskell98 From git at git.haskell.org Tue Dec 13 19:22:17 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:22:17 +0000 (UTC) Subject: [commit: packages/haskeline] master: Merge pull request #46 from bgamari/master (373ed5a) Message-ID: <20161213192217.490AF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/373ed5a09754b8c452c2393aa6808c0375dce13c >--------------------------------------------------------------- commit 373ed5a09754b8c452c2393aa6808c0375dce13c Merge: 7ac8df7 db4413d Author: Judah Jacobson Date: Tue Nov 15 17:06:34 2016 -0800 Merge pull request #46 from bgamari/master Bump upper bound on base >--------------------------------------------------------------- 373ed5a09754b8c452c2393aa6808c0375dce13c haskeline.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Tue Dec 13 19:22:19 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:22:19 +0000 (UTC) Subject: [commit: packages/haskeline] master: Bump directory upper bound to < 1.4 (8fd5b99) Message-ID: <20161213192219.4F0043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/8fd5b99666277a8f1f988dcd6d751f0d98b05668 >--------------------------------------------------------------- commit 8fd5b99666277a8f1f988dcd6d751f0d98b05668 Author: Ben Gamari Date: Tue Dec 6 17:41:16 2016 -0500 Bump directory upper bound to < 1.4 >--------------------------------------------------------------- 8fd5b99666277a8f1f988dcd6d751f0d98b05668 haskeline.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/haskeline.cabal b/haskeline.cabal index 1a9b86e..b7949de 100644 --- a/haskeline.cabal +++ b/haskeline.cabal @@ -43,7 +43,7 @@ Library -- though it was implemented in earlier releases, due to GHC bug #5436 which -- wasn't fixed until 7.4.1 Build-depends: base >=4.5 && < 4.11, containers>=0.4 && < 0.6, - directory>=1.1 && < 1.3, bytestring>=0.9 && < 0.11, + directory>=1.1 && < 1.4, bytestring>=0.9 && < 0.11, filepath >= 1.2 && < 1.5, transformers >= 0.2 && < 0.6 Default-Language: Haskell98 Default-Extensions: From git at git.haskell.org Tue Dec 13 19:22:21 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:22:21 +0000 (UTC) Subject: [commit: packages/haskeline] master: Merge pull request #48 from bgamari/master (3653874) Message-ID: <20161213192221.552043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/3653874be6a6b0df3077b7dee583c9aa442e2ebd >--------------------------------------------------------------- commit 3653874be6a6b0df3077b7dee583c9aa442e2ebd Merge: 373ed5a 8fd5b99 Author: Judah Jacobson Date: Fri Dec 9 09:50:31 2016 -0800 Merge pull request #48 from bgamari/master Bump directory upper bound to < 1.4 >--------------------------------------------------------------- 3653874be6a6b0df3077b7dee583c9aa442e2ebd haskeline.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Tue Dec 13 19:22:23 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:22:23 +0000 (UTC) Subject: [commit: packages/haskeline] master's head updated: Merge pull request #48 from bgamari/master (3653874) Message-ID: <20161213192223.7450F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline Branch 'master' now includes: e5ca1c5 Bump the lower requirement to 7.4.1. 8d0b3f7 Merge branch 'master' into bump-lower-dep 9673f11 Revert the hack that was specific to ghc-7.2.1. 50f640e Remove more obsolete #if's 82b2a66 Remove "LANGUAGE CPP" from Setup.hs 8a1c804 Clean up now-trivial functions in the Encoder module. d932f7f Bump the version to 0.7.3.0. 53c735d Adding threadsafe (in terminal-style interaction) ^Cternal print function. 0640f91 Extending concurrent print function to Win32 backend. 7502ca2 Fixing a trivial bug and a comment. a89ecc1 Point to github wiki 67488a5 Fixing a copy-pasting artifact. cb1a30c Merge pull request #37 from niobium0/external_print 0a5c8b0 Fix the behavior of unix-word-rubout (C-w) for emacs bindings e1a5161 Merge pull request #39 from watashi/unix_word_rubout da39fac Fix the behavior of unix-word-rubout (C-w) for emacs bindings (cherry picked from commit 0a5c8b05104ce109508bd24f733440a674fb8840) c5915d2 Point to github instead of trac. e5772f4 Merge branch 'issue-reporter' into release-0.7.2.3 8addaa2 Bump version to 0.7.2.3. cec24a1 Merge branch 'issue-reporter' 3600181 Merge branch 'master' into bump-lower-dep 80bfa5d Merge branch 'release-0.7.2.3' 3cf1bd3 Add Changelog for 0.7.3.0. df94abf Fix withInterrupt function docs f18a911 Merge pull request #41 from zaynetro/patch-1 13d2bd1 MonadFix instance for InputT c0e985e Merge pull request #42 from avieth/aovieth/monad_fix 08e972b .travis.yml: Add ghc 7.10.3 and 8.0.1 7ac8df7 Merge pull request #43 from erikd/master db4413d Bump upper bound on base 373ed5a Merge pull request #46 from bgamari/master 8fd5b99 Bump directory upper bound to < 1.4 3653874 Merge pull request #48 from bgamari/master From git at git.haskell.org Tue Dec 13 19:22:45 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:22:45 +0000 (UTC) Subject: [commit: packages/hpc] branch 'ghc-8.0' created Message-ID: <20161213192245.179013A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc New branch : ghc-8.0 Referencing: 25de22a34ec5770a3c4589e99817f5d116c35241 From git at git.haskell.org Tue Dec 13 19:22:47 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 19:22:47 +0000 (UTC) Subject: [commit: packages/hpc] ghc-8.0: Bump directory upper bound to <1.4 (25de22a) Message-ID: <20161213192247.1E08F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : ghc-8.0 Link : http://git.haskell.org/packages/hpc.git/commitdiff/25de22a34ec5770a3c4589e99817f5d116c35241 >--------------------------------------------------------------- commit 25de22a34ec5770a3c4589e99817f5d116c35241 Author: Ben Gamari Date: Tue Dec 6 17:21:24 2016 -0500 Bump directory upper bound to <1.4 (cherry picked from commit 8625c1c0550719437acad89d49401cf048990084) >--------------------------------------------------------------- 25de22a34ec5770a3c4589e99817f5d116c35241 hpc.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hpc.cabal b/hpc.cabal index 7e77973..be8ddd5 100644 --- a/hpc.cabal +++ b/hpc.cabal @@ -37,7 +37,7 @@ Library Build-Depends: base >= 4.4.1 && < 4.10, containers >= 0.4.1 && < 0.6, - directory >= 1.1 && < 1.3, + directory >= 1.1 && < 1.4, filepath >= 1 && < 1.5, time >= 1.2 && < 1.7 ghc-options: -Wall From git at git.haskell.org Tue Dec 13 20:08:15 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 20:08:15 +0000 (UTC) Subject: [commit: ghc] master: Fix recompilation detection when set of signatures to merge changes. (db23ccf) Message-ID: <20161213200815.76D463A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/db23ccfa2016902301a2fe71dedc2d6d3f3427be/ghc >--------------------------------------------------------------- commit db23ccfa2016902301a2fe71dedc2d6d3f3427be Author: Edward Z. Yang Date: Sun Dec 11 19:42:29 2016 -0800 Fix recompilation detection when set of signatures to merge changes. Summary: Previously, we only checked to recompile if a signature we previously depended on changed; however, if the -unit-id settings changed, this could have resulted in more or less signatures needing to be merged in; we weren't checking for this case. (Note that this logic is irrelevant for normal module imports, which we also check using -unit-id, as we record each import and redo it, forcing a recompile if the result changed.) Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2832 >--------------------------------------------------------------- db23ccfa2016902301a2fe71dedc2d6d3f3427be compiler/basicTypes/Module.hs | 22 +++++++++++++ compiler/iface/MkIface.hs | 19 +++++++++++- testsuite/driver/extra_files.py | 1 + .../tests/backpack/cabal/bkpcabal03/.gitignore | 1 + testsuite/tests/backpack/cabal/bkpcabal03/Makefile | 36 ++++++++++++++++++++++ testsuite/tests/backpack/cabal/bkpcabal03/Mod.hs | 4 +++ .../cabal/{bkpcabal01 => bkpcabal03}/Setup.hs | 0 .../T12733 => backpack/cabal/bkpcabal03}/all.T | 4 +-- .../tests/backpack/cabal/bkpcabal03/asig1/A.hsig | 2 ++ .../backpack/cabal/bkpcabal03/asig1/asig1.cabal | 12 ++++++++ .../tests/backpack/cabal/bkpcabal03/asig2/A.hsig | 2 ++ .../backpack/cabal/bkpcabal03/asig2/asig2.cabal | 12 ++++++++ .../backpack/cabal/bkpcabal03/bkpcabal03.cabal.in1 | 12 ++++++++ .../backpack/cabal/bkpcabal03/bkpcabal03.cabal.in2 | 12 ++++++++ .../backpack/cabal/bkpcabal03/bkpcabal03.stderr | 2 ++ 15 files changed, 138 insertions(+), 3 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc db23ccfa2016902301a2fe71dedc2d6d3f3427be From git at git.haskell.org Tue Dec 13 20:54:10 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 20:54:10 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: testsuite: Bump down allocations of T3064 (9ac7335) Message-ID: <20161213205410.E50CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/9ac7335f23ed6887ec728deb28ded9c53986fabd/ghc >--------------------------------------------------------------- commit 9ac7335f23ed6887ec728deb28ded9c53986fabd Author: Ben Gamari Date: Mon Dec 12 16:16:15 2016 -0500 testsuite: Bump down allocations of T3064 >--------------------------------------------------------------- 9ac7335f23ed6887ec728deb28ded9c53986fabd testsuite/tests/perf/compiler/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 89d9316..06bc981 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -280,7 +280,7 @@ test('T3064', # 2014-01-22: 23 (x86/Linux) # 2014-12-22: 23 (x86/Linux) death to silent superclasses # 2015-07-11 28 (x86/Linux, 64-bit machine) use +RTS -G1 - (wordsize(64), 66, 20)]), + (wordsize(64), 49, 20)]), # (amd64/Linux): 18 # (amd64/Linux) 2012-02-07: 26 # (amd64/Linux) 2013-02-12: 23; increased range to 10% @@ -295,6 +295,7 @@ test('T3064', # (amd64/Linux) 2015-01-22: 32: Varies from 30 to 34, at least here. # (amd64/Linux) 2015-06-03: 54: use +RTS -G1 # (amd64/Linux) 2016-11-03: 66: Parenthesis reading for Read + # (amd64/Linux) 2016-12-12: 49: Unknown compiler_stats_num_field('bytes allocated', [(wordsize(32), 153261024, 10), From git at git.haskell.org Tue Dec 13 20:54:13 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 20:54:13 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Bump directory submodule to 1.3.0.0 and Cabal to 1.24.2.0 (6c6f9c1) Message-ID: <20161213205413.9A6F83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/6c6f9c1de4a548afccb3f5c557600987e87cb11e/ghc >--------------------------------------------------------------- commit 6c6f9c1de4a548afccb3f5c557600987e87cb11e Author: Ben Gamari Date: Tue Dec 6 14:22:52 2016 -0500 Bump directory submodule to 1.3.0.0 and Cabal to 1.24.2.0 >--------------------------------------------------------------- 6c6f9c1de4a548afccb3f5c557600987e87cb11e compiler/ghc.cabal.in | 2 +- ghc/ghc-bin.cabal.in | 2 +- libraries/Cabal | 2 +- libraries/directory | 2 +- libraries/ghc-boot/ghc-boot.cabal.in | 2 +- libraries/haskeline | 2 +- libraries/hpc | 2 +- libraries/process | 2 +- utils/ghc-cabal/ghc-cabal.cabal | 2 +- utils/ghc-pkg/ghc-pkg.cabal | 2 +- utils/ghc-pwd/ghc-pwd.cabal | 3 +-- utils/hpc/hpc-bin.cabal | 2 +- utils/hsc2hs | 2 +- utils/runghc/runghc.cabal.in | 2 +- 14 files changed, 14 insertions(+), 15 deletions(-) diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index 4d5e3b5..e0aee80 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -46,7 +46,7 @@ Library Build-Depends: base >= 4 && < 5, deepseq >= 1.3 && < 1.5, - directory >= 1 && < 1.3, + directory >= 1 && < 1.4, process >= 1 && < 1.5, bytestring >= 0.9 && < 0.11, binary == 0.8.*, diff --git a/ghc/ghc-bin.cabal.in b/ghc/ghc-bin.cabal.in index 9d4125a..b9babfe 100644 --- a/ghc/ghc-bin.cabal.in +++ b/ghc/ghc-bin.cabal.in @@ -31,7 +31,7 @@ Executable ghc Build-Depends: base >= 4 && < 5, array >= 0.1 && < 0.6, bytestring >= 0.9 && < 0.11, - directory >= 1 && < 1.3, + directory >= 1 && < 1.4, process >= 1 && < 1.5, filepath >= 1 && < 1.5, ghc-boot == @ProjectVersionMunged@, diff --git a/libraries/Cabal b/libraries/Cabal index 51ff8b6..8180b67 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 51ff8b66468977dcccb81d19ac2d42ee27c9ccd1 +Subproject commit 8180b67a130c91079a5197177b005be2c4124fff diff --git a/libraries/directory b/libraries/directory index ad2e0a1..65d1d85 160000 --- a/libraries/directory +++ b/libraries/directory @@ -1 +1 @@ -Subproject commit ad2e0a110bf2ee2e2a3bd87963fa55505ca58b28 +Subproject commit 65d1d85a3fc3373a425a0298d572da9cd9ee3d86 diff --git a/libraries/ghc-boot/ghc-boot.cabal.in b/libraries/ghc-boot/ghc-boot.cabal.in index 6375b8b..2a1ceb3 100644 --- a/libraries/ghc-boot/ghc-boot.cabal.in +++ b/libraries/ghc-boot/ghc-boot.cabal.in @@ -44,6 +44,6 @@ Library build-depends: base >= 4.7 && < 4.10, binary == 0.8.*, bytestring == 0.10.*, - directory == 1.2.*, + directory >= 1.2 && < 1.4, filepath >= 1.3 && < 1.5, ghc-boot-th == @ProjectVersionMunged@ diff --git a/libraries/haskeline b/libraries/haskeline index 8addaa2..3653874 160000 --- a/libraries/haskeline +++ b/libraries/haskeline @@ -1 +1 @@ -Subproject commit 8addaa2f6f4256da76bac4075316597d0b1d8f67 +Subproject commit 3653874be6a6b0df3077b7dee583c9aa442e2ebd diff --git a/libraries/hpc b/libraries/hpc index 88b389f..25de22a 160000 --- a/libraries/hpc +++ b/libraries/hpc @@ -1 +1 @@ -Subproject commit 88b389f368d1222078ee9592236b107d061cd5f2 +Subproject commit 25de22a34ec5770a3c4589e99817f5d116c35241 diff --git a/libraries/process b/libraries/process index 296cbce..85cc1d1 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit 296cbce6294316d6534b4449fc7ab0f0d3f5775b +Subproject commit 85cc1d17e9550a075003a764a2429d4acde65159 diff --git a/utils/ghc-cabal/ghc-cabal.cabal b/utils/ghc-cabal/ghc-cabal.cabal index 78a0f22..feffe3e 100644 --- a/utils/ghc-cabal/ghc-cabal.cabal +++ b/utils/ghc-cabal/ghc-cabal.cabal @@ -22,6 +22,6 @@ Executable ghc-cabal Build-Depends: base >= 3 && < 5, bytestring >= 0.10 && < 0.11, Cabal == 1.24.*, - directory >= 1.1 && < 1.3, + directory >= 1.1 && < 1.4, filepath >= 1.2 && < 1.5 diff --git a/utils/ghc-pkg/ghc-pkg.cabal b/utils/ghc-pkg/ghc-pkg.cabal index 5f76e1b..3511e36 100644 --- a/utils/ghc-pkg/ghc-pkg.cabal +++ b/utils/ghc-pkg/ghc-pkg.cabal @@ -22,7 +22,7 @@ Executable ghc-pkg Other-Extensions: CPP Build-Depends: base >= 4 && < 5, - directory >= 1 && < 1.3, + directory >= 1 && < 1.4, process >= 1 && < 1.5, containers, filepath, diff --git a/utils/ghc-pwd/ghc-pwd.cabal b/utils/ghc-pwd/ghc-pwd.cabal index dcd9529..1b18761 100644 --- a/utils/ghc-pwd/ghc-pwd.cabal +++ b/utils/ghc-pwd/ghc-pwd.cabal @@ -15,5 +15,4 @@ Executable ghc-pwd Default-Language: Haskell2010 Main-Is: Main.hs Build-Depends: base >= 3 && < 5, - directory >= 1 && < 1.3 - + directory >= 1 && < 1.4 diff --git a/utils/hpc/hpc-bin.cabal b/utils/hpc/hpc-bin.cabal index 87c5b11..e83a45d 100644 --- a/utils/hpc/hpc-bin.cabal +++ b/utils/hpc/hpc-bin.cabal @@ -29,7 +29,7 @@ Executable hpc Paths_hpc_bin Build-Depends: base >= 4 && < 5, - directory >= 1 && < 1.3, + directory >= 1 && < 1.4, filepath >= 1 && < 1.5, containers >= 0.1 && < 0.6, array >= 0.1 && < 0.6, diff --git a/utils/hsc2hs b/utils/hsc2hs index 8fed36a..fbc552f 160000 --- a/utils/hsc2hs +++ b/utils/hsc2hs @@ -1 +1 @@ -Subproject commit 8fed36addd3439e01752a0ce48140ad0a56a6c61 +Subproject commit fbc552f4bb003edbdd52305a5eb34a903c9fe625 diff --git a/utils/runghc/runghc.cabal.in b/utils/runghc/runghc.cabal.in index 2253292..3be9f26 100644 --- a/utils/runghc/runghc.cabal.in +++ b/utils/runghc/runghc.cabal.in @@ -27,7 +27,7 @@ Executable runghc Main-Is: Main.hs Build-Depends: base >= 3 && < 5, - directory >= 1 && < 1.3, + directory >= 1 && < 1.4, process >= 1 && < 1.5, filepath From git at git.haskell.org Tue Dec 13 21:23:53 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 21:23:53 +0000 (UTC) Subject: [commit: ghc] master: Revert "Float unboxed expressions by boxing" (f723ba2) Message-ID: <20161213212353.ADEE23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f723ba2f3b6d778f903fb1de4a5af93fe65eed10/ghc >--------------------------------------------------------------- commit f723ba2f3b6d778f903fb1de4a5af93fe65eed10 Author: Ben Gamari Date: Tue Dec 13 14:42:10 2016 -0500 Revert "Float unboxed expressions by boxing" This reverts commit bc3d37dada357b04fc5a35f740b4fe7e05292b06. >--------------------------------------------------------------- f723ba2f3b6d778f903fb1de4a5af93fe65eed10 compiler/prelude/TysPrim.hs | 12 +- compiler/prelude/TysWiredIn.hs | 28 ---- compiler/simplCore/SetLevels.hs | 155 +++++++-------------- testsuite/tests/simplCore/should_compile/Makefile | 4 - testsuite/tests/simplCore/should_compile/T12603.hs | 45 ------ .../tests/simplCore/should_compile/T12603.stdout | 1 - testsuite/tests/simplCore/should_compile/all.T | 4 - 7 files changed, 54 insertions(+), 195 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f723ba2f3b6d778f903fb1de4a5af93fe65eed10 From git at git.haskell.org Tue Dec 13 21:23:56 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 21:23:56 +0000 (UTC) Subject: [commit: ghc] master: base: Make raw buffer IO operations more strict (cc2e3ec) Message-ID: <20161213212356.691113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cc2e3ec06ce5ac979ff2ecf453ad85b0e5ff326d/ghc >--------------------------------------------------------------- commit cc2e3ec06ce5ac979ff2ecf453ad85b0e5ff326d Author: Ben Gamari Date: Tue Dec 13 14:49:20 2016 -0500 base: Make raw buffer IO operations more strict Ticket #9696 reported that `readRawBufferPtr` and `writeRawBufferPtr` allocated unnecessarily. The binding is question was, ``` let { buf_s4VD [Dmd=] :: GHC.Ptr.Ptr GHC.Word.Word8 [LclId, Unf=OtherCon []] = NO_CCS GHC.Ptr.Ptr! [ds1_s4Vy]; } in case GHC.IO.FD.$wreadRawBufferPtr Main.main5 0# 0# buf_s4VD Main.main4 Main.main3 GHC.Prim.void# of ... ``` The problem was that GHC apparently couldn't tell that `readRawBufferPtr` would always demand the buffer. Here we simple add bang patterns on all of the small arguments of these functions to ensure that worker/wrappers can eliminate these allocations. Test Plan: Look at STG produced by testcase in #9696, verify no allocations Reviewers: austin, hvr, simonmar Reviewed By: simonmar Subscribers: RyanGlScott, simonmar, thomie Differential Revision: https://phabricator.haskell.org/D2813 GHC Trac Issues: #9696 >--------------------------------------------------------------- cc2e3ec06ce5ac979ff2ecf453ad85b0e5ff326d libraries/base/GHC/IO/FD.hs | 20 ++++++++++---------- libraries/base/changelog.md | 2 ++ 2 files changed, 12 insertions(+), 10 deletions(-) diff --git a/libraries/base/GHC/IO/FD.hs b/libraries/base/GHC/IO/FD.hs index 381f39a..82ba628 100644 --- a/libraries/base/GHC/IO/FD.hs +++ b/libraries/base/GHC/IO/FD.hs @@ -500,7 +500,7 @@ indicates that there's no data, we call threadWaitRead. -} readRawBufferPtr :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO Int -readRawBufferPtr loc !fd buf off len +readRawBufferPtr loc !fd !buf !off !len | isNonBlocking fd = unsafe_read -- unsafe is ok, it can't block | otherwise = do r <- throwErrnoIfMinus1 loc (unsafe_fdReady (fdFD fd) 0 0 0) @@ -517,7 +517,7 @@ readRawBufferPtr loc !fd buf off len -- return: -1 indicates EOF, >=0 is bytes read readRawBufferPtrNoBlock :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO Int -readRawBufferPtrNoBlock loc !fd buf off len +readRawBufferPtrNoBlock loc !fd !buf !off !len | isNonBlocking fd = unsafe_read -- unsafe is ok, it can't block | otherwise = do r <- unsafe_fdReady (fdFD fd) 0 0 0 if r /= 0 then safe_read @@ -533,7 +533,7 @@ readRawBufferPtrNoBlock loc !fd buf off len safe_read = do_read (c_safe_read (fdFD fd) (buf `plusPtr` off) len) writeRawBufferPtr :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO CInt -writeRawBufferPtr loc !fd buf off len +writeRawBufferPtr loc !fd !buf !off !len | isNonBlocking fd = unsafe_write -- unsafe is ok, it can't block | otherwise = do r <- unsafe_fdReady (fdFD fd) 1 0 0 if r /= 0 @@ -548,7 +548,7 @@ writeRawBufferPtr loc !fd buf off len safe_write = do_write (c_safe_write (fdFD fd) (buf `plusPtr` off) len) writeRawBufferPtrNoBlock :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO CInt -writeRawBufferPtrNoBlock loc !fd buf off len +writeRawBufferPtrNoBlock loc !fd !buf !off !len | isNonBlocking fd = unsafe_write -- unsafe is ok, it can't block | otherwise = do r <- unsafe_fdReady (fdFD fd) 1 0 0 if r /= 0 then write @@ -571,12 +571,12 @@ foreign import ccall unsafe "fdReady" #else /* mingw32_HOST_OS.... */ readRawBufferPtr :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO CInt -readRawBufferPtr loc !fd buf off len +readRawBufferPtr loc !fd !buf !off !len | threaded = blockingReadRawBufferPtr loc fd buf off len | otherwise = asyncReadRawBufferPtr loc fd buf off len writeRawBufferPtr :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO CInt -writeRawBufferPtr loc !fd buf off len +writeRawBufferPtr loc !fd !buf !off !len | threaded = blockingWriteRawBufferPtr loc fd buf off len | otherwise = asyncWriteRawBufferPtr loc fd buf off len @@ -589,7 +589,7 @@ writeRawBufferPtrNoBlock = writeRawBufferPtr -- Async versions of the read/write primitives, for the non-threaded RTS asyncReadRawBufferPtr :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO CInt -asyncReadRawBufferPtr loc !fd buf off len = do +asyncReadRawBufferPtr loc !fd !buf !off !len = do (l, rc) <- asyncRead (fromIntegral (fdFD fd)) (fdIsSocket_ fd) (fromIntegral len) (buf `plusPtr` off) if l == (-1) @@ -598,7 +598,7 @@ asyncReadRawBufferPtr loc !fd buf off len = do else return (fromIntegral l) asyncWriteRawBufferPtr :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO CInt -asyncWriteRawBufferPtr loc !fd buf off len = do +asyncWriteRawBufferPtr loc !fd !buf !off !len = do (l, rc) <- asyncWrite (fromIntegral (fdFD fd)) (fdIsSocket_ fd) (fromIntegral len) (buf `plusPtr` off) if l == (-1) @@ -609,14 +609,14 @@ asyncWriteRawBufferPtr loc !fd buf off len = do -- Blocking versions of the read/write primitives, for the threaded RTS blockingReadRawBufferPtr :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO CInt -blockingReadRawBufferPtr loc fd buf off len +blockingReadRawBufferPtr loc !fd !buf !off !len = throwErrnoIfMinus1Retry loc $ if fdIsSocket fd then c_safe_recv (fdFD fd) (buf `plusPtr` off) (fromIntegral len) 0 else c_safe_read (fdFD fd) (buf `plusPtr` off) (fromIntegral len) blockingWriteRawBufferPtr :: String -> FD -> Ptr Word8-> Int -> CSize -> IO CInt -blockingWriteRawBufferPtr loc fd buf off len +blockingWriteRawBufferPtr loc !fd !buf !off !len = throwErrnoIfMinus1Retry loc $ if fdIsSocket fd then c_safe_send (fdFD fd) (buf `plusPtr` off) (fromIntegral len) 0 diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 5983747..5039b64 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -30,6 +30,8 @@ * Added `Eq1`, `Ord1`, `Read1` and `Show1` instances for `NonEmpty`. + * Raw buffer operations in `GHC.IO.FD` are now strict in the buffer, offset, and length operations (#9696) + ## 4.9.0.0 *May 2016* * Bundled with GHC 8.0 From git at git.haskell.org Tue Dec 13 21:23:59 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 21:23:59 +0000 (UTC) Subject: [commit: ghc] master: Don't have CPP macros expanding to 'defined'. (cb582b6) Message-ID: <20161213212359.1F08F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cb582b6476f64c1c86d89dce4d78462581fd2a6f/ghc >--------------------------------------------------------------- commit cb582b6476f64c1c86d89dce4d78462581fd2a6f Author: Shea Levy Date: Tue Dec 13 14:53:50 2016 -0500 Don't have CPP macros expanding to 'defined'. Reviewers: austin, simonmar, erikd, bgamari Reviewed By: erikd, bgamari Subscribers: angerman, thomie Differential Revision: https://phabricator.haskell.org/D2823 >--------------------------------------------------------------- cb582b6476f64c1c86d89dce4d78462581fd2a6f includes/rts/storage/ClosureMacros.h | 13 +++++++++++-- 1 file changed, 11 insertions(+), 2 deletions(-) diff --git a/includes/rts/storage/ClosureMacros.h b/includes/rts/storage/ClosureMacros.h index 90198f2..c8c270f 100644 --- a/includes/rts/storage/ClosureMacros.h +++ b/includes/rts/storage/ClosureMacros.h @@ -520,8 +520,17 @@ INLINE_HEADER StgWord8 *mutArrPtrsCard (StgMutArrPtrs *a, W_ n) -------------------------------------------------------------------------- */ -#define ZERO_SLOP_FOR_LDV_PROF (defined(PROFILING)) -#define ZERO_SLOP_FOR_SANITY_CHECK (defined(DEBUG) && !defined(THREADED_RTS)) +#if defined(PROFILING) +#define ZERO_SLOP_FOR_LDV_PROF 1 +#else +#define ZERO_SLOP_FOR_LDV_PROF 0 +#endif + +#if defined(DEBUG) && !defined(THREADED_RTS) +#define ZERO_SLOP_FOR_SANITY_CHECK 1 +#else +#define ZERO_SLOP_FOR_SANITY_CHECK 0 +#endif #if ZERO_SLOP_FOR_LDV_PROF || ZERO_SLOP_FOR_SANITY_CHECK #define OVERWRITING_CLOSURE(c) overwritingClosure(c) From git at git.haskell.org Tue Dec 13 21:24:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 21:24:01 +0000 (UTC) Subject: [commit: ghc] master: Fix testcase T12903 on OS X (aa123f4) Message-ID: <20161213212401.CD90C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/aa123f445338c2980fcee87a09c01d14a83bf409/ghc >--------------------------------------------------------------- commit aa123f445338c2980fcee87a09c01d14a83bf409 Author: Alexander Vershilov Date: Tue Dec 13 14:54:36 2016 -0500 Fix testcase T12903 on OS X Old test used timeouts that leads to the various sporadic errors. Tet was rewritten to not use timeouts. Reviewers: austin, erikd, simonmar, bgamari Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2827 GHC Trac Issues: #12956 >--------------------------------------------------------------- aa123f445338c2980fcee87a09c01d14a83bf409 testsuite/tests/rts/T12903.hs | 17 ++++++++++++++--- testsuite/tests/rts/all.T | 6 +----- 2 files changed, 15 insertions(+), 8 deletions(-) diff --git a/testsuite/tests/rts/T12903.hs b/testsuite/tests/rts/T12903.hs index ddaf8b9..e4a8486 100644 --- a/testsuite/tests/rts/T12903.hs +++ b/testsuite/tests/rts/T12903.hs @@ -1,10 +1,21 @@ import Control.Concurrent import Control.Exception +import System.IO import System.Posix +import System.Posix.IO main = do + (pout1, pin1) <- createPipe + (pout2, _) <- createPipe pid <- forkProcess $ do - handle (\UserInterrupt{} -> putStrLn "caught") - $ threadDelay 2000000 + hdl <- fdToHandle pin1 + hSetBuffering hdl LineBuffering + handle (\UserInterrupt{} -> hPutStrLn hdl "caught") + $ do hPutStrLn hdl "registered" + hdl2 <- fdToHandle pout2 + putStrLn =<< hGetLine hdl2 + hdl <- fdToHandle pout1 + hSetBuffering hdl LineBuffering + "registered" <- hGetLine hdl signalProcess sigINT pid - threadDelay 2000000 + putStrLn =<< hGetLine hdl diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index c44ec04..a645ad3 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -376,9 +376,5 @@ test('T12497', [ unless(opsys('mingw32'), skip) ], run_command, ['$MAKE -s --no-print-directory T12497']) -# Test is being skipped on darwin due to it's flakiness. -# See 12956 -test('T12903', [when(opsys('mingw32'), skip), - when(opsys('darwin'), skip)], - compile_and_run, ['']) +test('T12903', [when(opsys('mingw32'), skip)], compile_and_run, ['']) From git at git.haskell.org Tue Dec 13 21:24:04 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 21:24:04 +0000 (UTC) Subject: [commit: ghc] master: Fix Win32 x86 build validation after D2756 (9cb4a13) Message-ID: <20161213212404.956C83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9cb4a130a5ed16ed95b8cab90cefe23dbae9a337/ghc >--------------------------------------------------------------- commit 9cb4a130a5ed16ed95b8cab90cefe23dbae9a337 Author: Tamar Christina Date: Tue Dec 13 14:54:09 2016 -0500 Fix Win32 x86 build validation after D2756 Test Plan: ./validate Reviewers: austin, bgamari, erikd, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2825 >--------------------------------------------------------------- 9cb4a130a5ed16ed95b8cab90cefe23dbae9a337 rts/Stats.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/Stats.c b/rts/Stats.c index 767a36f..217bace 100644 --- a/rts/Stats.c +++ b/rts/Stats.c @@ -398,7 +398,7 @@ stat_endGC (Capability *cap, gc_thread *gct, if (RtsFlags.GcFlags.giveStats == VERBOSE_GC_STATS) { W_ faults = getPageFaults(); - statsPrintf("%9" FMT_Word " %9" FMT_Word " %9" FMT_Word, + statsPrintf("%9" FMT_Word64 " %9" FMT_Word64 " %9" FMT_Word64, stats.gc.allocated_bytes, stats.gc.copied_bytes, stats.gc.live_bytes); From git at git.haskell.org Tue Dec 13 21:24:07 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 21:24:07 +0000 (UTC) Subject: [commit: ghc] master: print * in unicode correctly (fixes #12550) (7031704) Message-ID: <20161213212407.542D43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7031704332db55de1fc3c46a8f450bad933997e0/ghc >--------------------------------------------------------------- commit 7031704332db55de1fc3c46a8f450bad933997e0 Author: John Leo Date: Tue Dec 13 14:57:15 2016 -0500 print * in unicode correctly (fixes #12550) Test Plan: validate Reviewers: simonpj, austin, bgamari, goldfire Reviewed By: bgamari, goldfire Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2829 >--------------------------------------------------------------- 7031704332db55de1fc3c46a8f450bad933997e0 compiler/basicTypes/BasicTypes.hs | 2 +- compiler/iface/IfaceType.hs | 21 ++++++------ compiler/types/TyCoRep.hs | 4 +-- compiler/utils/Outputable.hs | 5 ++- .../tests/generics/T10604/T10604_deriving.stderr | 38 +++++++++++----------- testsuite/tests/ghci/scripts/T12550.script | 38 ++++++++++++++++++++-- testsuite/tests/ghci/scripts/T12550.stdout | 14 ++++++++ testsuite/tests/ghci/scripts/all.T | 2 +- 8 files changed, 88 insertions(+), 36 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7031704332db55de1fc3c46a8f450bad933997e0 From git at git.haskell.org Tue Dec 13 21:24:10 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 21:24:10 +0000 (UTC) Subject: [commit: ghc] master: Fix pretty printing of top level SCC pragmas (8ec864d) Message-ID: <20161213212410.7B3DF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8ec864d08c09a8aa7aabc4abf30186e5f3995ad4/ghc >--------------------------------------------------------------- commit 8ec864d08c09a8aa7aabc4abf30186e5f3995ad4 Author: Matthew Pickering Date: Tue Dec 13 14:59:35 2016 -0500 Fix pretty printing of top level SCC pragmas Reviewers: austin, alanz, bgamari Reviewed By: alanz, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2834 >--------------------------------------------------------------- 8ec864d08c09a8aa7aabc4abf30186e5f3995ad4 compiler/hsSyn/HsBinds.hs | 6 ++---- testsuite/tests/printer/Makefile | 4 ++++ testsuite/tests/printer/Ppr048.hs | 9 +++++++++ testsuite/tests/printer/all.T | 1 + 4 files changed, 16 insertions(+), 4 deletions(-) diff --git a/compiler/hsSyn/HsBinds.hs b/compiler/hsSyn/HsBinds.hs index 1f58bbf..5933df8 100644 --- a/compiler/hsSyn/HsBinds.hs +++ b/compiler/hsSyn/HsBinds.hs @@ -975,10 +975,8 @@ ppr_sig (SpecInstSig src ty) ppr_sig (MinimalSig _ bf) = pragBrackets (pprMinimalSig bf) ppr_sig (PatSynSig names sig_ty) = text "pattern" <+> pprVarSig (map unLoc names) (ppr sig_ty) -ppr_sig (SCCFunSig _ fn Nothing) - = pragBrackets (text "SCC" <+> ppr fn) -ppr_sig (SCCFunSig src fn (Just str)) - = pragSrcBrackets src "{-# SCC#-}" (ppr fn <+> ppr str) +ppr_sig (SCCFunSig src fn mlabel) + = pragSrcBrackets src "{-# SCC" (ppr fn <+> maybe empty ppr mlabel ) instance OutputableBndr name => Outputable (FixitySig name) where ppr (FixitySig names fixity) = sep [ppr fixity, pprops] diff --git a/testsuite/tests/printer/Makefile b/testsuite/tests/printer/Makefile index b21419c..7a6bbc5 100644 --- a/testsuite/tests/printer/Makefile +++ b/testsuite/tests/printer/Makefile @@ -193,3 +193,7 @@ ppr046: .PHONY: ppr047 ppr047: $(CHECK_PPR) "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" Ppr047.hs + +.PHONY: ppr048 +ppr048: + $(CHECK_PPR) "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" Ppr048.hs diff --git a/testsuite/tests/printer/Ppr048.hs b/testsuite/tests/printer/Ppr048.hs new file mode 100644 index 0000000..83322f8 --- /dev/null +++ b/testsuite/tests/printer/Ppr048.hs @@ -0,0 +1,9 @@ +module Ppr048 where + +{-# SCc foo #-} +foo :: Int -> Int +foo x = x + +{-# SCc foo2 "label" #-} +foo2 :: () +foo2 = () diff --git a/testsuite/tests/printer/all.T b/testsuite/tests/printer/all.T index 701d678..e0cfcc2 100644 --- a/testsuite/tests/printer/all.T +++ b/testsuite/tests/printer/all.T @@ -45,3 +45,4 @@ test('Ppr044', ignore_stderr, run_command, ['$MAKE -s --no-print-directory ppr04 test('Ppr045', ignore_stderr, run_command, ['$MAKE -s --no-print-directory ppr045']) test('Ppr046', ignore_stderr, run_command, ['$MAKE -s --no-print-directory ppr046']) test('Ppr047', expect_fail, run_command, ['$MAKE -s --no-print-directory ppr047']) +test('Ppr048', ignore_stderr, run_command, ['$MAKE -s --no-print-directory ppr048']) From git at git.haskell.org Tue Dec 13 22:48:25 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Dec 2016 22:48:25 +0000 (UTC) Subject: [commit: ghc] wip/rae: Checkpoint toward new levity polymorphism (eaa8aee) Message-ID: <20161213224825.920473A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/eaa8aee80072ac2ff8a072a3d63c299155420ce4/ghc >--------------------------------------------------------------- commit eaa8aee80072ac2ff8a072a3d63c299155420ce4 Author: Richard Eisenberg Date: Tue Dec 13 17:43:32 2016 -0500 Checkpoint toward new levity polymorphism >--------------------------------------------------------------- eaa8aee80072ac2ff8a072a3d63c299155420ce4 compiler/cmm/CmmUtils.hs | 4 +- compiler/codeGen/StgCmm.hs | 6 +- compiler/codeGen/StgCmmClosure.hs | 10 +- compiler/codeGen/StgCmmEnv.hs | 5 +- compiler/codeGen/StgCmmForeign.hs | 11 +- compiler/codeGen/StgCmmUtils.hs | 6 +- compiler/coreSyn/CoreLint.hs | 15 +- compiler/deSugar/DsForeign.hs | 7 +- compiler/ghci/ByteCodeGen.hs | 60 ++++---- compiler/ghci/ByteCodeItbls.hs | 4 +- compiler/ghci/RtClosureInspect.hs | 29 ++-- compiler/iface/IfaceType.hs | 22 +-- compiler/main/InteractiveEval.hs | 5 +- compiler/prelude/PrelNames.hs | 16 +- compiler/prelude/PrimOp.hs | 8 +- compiler/prelude/TysPrim.hs | 118 +++++++-------- compiler/prelude/TysWiredIn.hs | 168 +++++++++++++++------ compiler/simplStg/RepType.hs | 305 ++++++++++++++++++-------------------- compiler/simplStg/UnariseStg.hs | 52 ++++--- compiler/stgSyn/CoreToStg.hs | 3 +- compiler/stgSyn/StgLint.hs | 4 +- compiler/stgSyn/StgSyn.hs | 4 +- compiler/typecheck/TcErrors.hs | 15 +- compiler/typecheck/TcHsSyn.hs | 104 +++---------- compiler/typecheck/TcHsType.hs | 13 +- compiler/typecheck/TcMType.hs | 2 +- compiler/typecheck/TcSimplify.hs | 13 +- compiler/typecheck/TcType.hs | 8 +- compiler/types/FamInstEnv.hs | 2 - compiler/types/Kind.hs | 2 +- compiler/types/TyCoRep.hs | 6 +- compiler/types/TyCon.hs | 2 +- compiler/types/Type.hs | 5 +- libraries/ghc-prim/GHC/Types.hs | 16 +- 34 files changed, 501 insertions(+), 549 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc eaa8aee80072ac2ff8a072a3d63c299155420ce4 From git at git.haskell.org Wed Dec 14 02:18:39 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Dec 2016 02:18:39 +0000 (UTC) Subject: [commit: ghc] wip/rae: Update levity polymorphism (07ce8da) Message-ID: <20161214021839.92A453A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/07ce8dab0091152ab8424eadecd67fe6d88b1ffb/ghc >--------------------------------------------------------------- commit 07ce8dab0091152ab8424eadecd67fe6d88b1ffb Author: Richard Eisenberg Date: Tue Dec 13 17:43:32 2016 -0500 Update levity polymorphism This commit implements the proposal in https://github.com/ghc-proposals/ghc-proposals/pull/29. Here are some of the pieces of that proposal: * Some of RuntimeRep's constructors have been shortened. * TupleRep and SumRep are now parameterized over a list of RuntimeReps. This means that two types with the same kind surely have the same representation. Previously, all unboxed tuples had the same kind, and thus the fact above was false. * RepType.typePrimRep and friends now return a *list* of PrimReps. These functions can now work successfully on unboxed tuples. This change is necessary because we allow abstraction over unboxed tuple types and so cannot always handle unboxed tuples specially as we did before. * The RepType.RepType type was removed, as it didn't seem to help with much. * The RepType.repType function is also removed, in favor of typePrimRep. * I have waffled a good deal on whether or not to keep VoidRep in TyCon.PrimRep. In the end, I decided to keep it there. PrimRep is *not* represented in RuntimeRep, and typePrimRep will never return a list including VoidRep. But it's handy to have in, e.g., ByteCodeGen and friends. I can imagine another design choice where we have a PrimRepV type that is PrimRep with an extra constructor. That seemed to be a heavier design, though, and I'm not sure what the benefit would be. * The last, unused vestiges of # (unliftedTypeKind) have been removed. >--------------------------------------------------------------- 07ce8dab0091152ab8424eadecd67fe6d88b1ffb compiler/cmm/CmmUtils.hs | 4 +- compiler/codeGen/StgCmm.hs | 6 +- compiler/codeGen/StgCmmClosure.hs | 10 +- compiler/codeGen/StgCmmEnv.hs | 5 +- compiler/codeGen/StgCmmForeign.hs | 11 +- compiler/codeGen/StgCmmUtils.hs | 6 +- compiler/coreSyn/CoreLint.hs | 15 +- compiler/deSugar/DsForeign.hs | 7 +- compiler/ghci/ByteCodeGen.hs | 60 ++++---- compiler/ghci/ByteCodeItbls.hs | 4 +- compiler/ghci/RtClosureInspect.hs | 29 ++-- compiler/iface/IfaceType.hs | 22 +-- compiler/main/InteractiveEval.hs | 5 +- compiler/prelude/PrelNames.hs | 16 +- compiler/prelude/PrimOp.hs | 8 +- compiler/prelude/TysPrim.hs | 118 +++++++-------- compiler/prelude/TysWiredIn.hs | 168 +++++++++++++++------ compiler/simplStg/RepType.hs | 305 ++++++++++++++++++-------------------- compiler/simplStg/UnariseStg.hs | 52 ++++--- compiler/stgSyn/CoreToStg.hs | 3 +- compiler/stgSyn/StgLint.hs | 4 +- compiler/stgSyn/StgSyn.hs | 4 +- compiler/typecheck/TcErrors.hs | 15 +- compiler/typecheck/TcHsSyn.hs | 104 +++---------- compiler/typecheck/TcHsType.hs | 13 +- compiler/typecheck/TcMType.hs | 2 +- compiler/typecheck/TcSimplify.hs | 13 +- compiler/typecheck/TcType.hs | 8 +- compiler/types/FamInstEnv.hs | 2 - compiler/types/Kind.hs | 2 +- compiler/types/TyCoRep.hs | 6 +- compiler/types/TyCon.hs | 2 +- compiler/types/Type.hs | 5 +- libraries/ghc-prim/GHC/Types.hs | 16 +- 34 files changed, 501 insertions(+), 549 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 07ce8dab0091152ab8424eadecd67fe6d88b1ffb From git at git.haskell.org Wed Dec 14 03:01:15 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Dec 2016 03:01:15 +0000 (UTC) Subject: [commit: ghc] master: Load orphan interfaces before checking if module implements signature (9c9a222) Message-ID: <20161214030115.5FF8F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9c9a2229fe741c55a8fb8d0c6380ec066a77722b/ghc >--------------------------------------------------------------- commit 9c9a2229fe741c55a8fb8d0c6380ec066a77722b Author: Edward Z. Yang Date: Tue Dec 13 18:03:47 2016 -0800 Load orphan interfaces before checking if module implements signature Summary: If we didn't load the orphans, we might conclude an instance is not implemented when it is. See test bkp42. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2841 >--------------------------------------------------------------- 9c9a2229fe741c55a8fb8d0c6380ec066a77722b compiler/typecheck/TcBackpack.hs | 5 +++++ testsuite/tests/backpack/should_compile/all.T | 1 + .../tests/backpack/should_compile/{bkp41.bkp => bkp42.bkp} | 9 ++++++--- testsuite/tests/backpack/should_compile/bkp42.stderr | 14 ++++++++++++++ 4 files changed, 26 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcBackpack.hs b/compiler/typecheck/TcBackpack.hs index b6623cd..1cf3393 100644 --- a/compiler/typecheck/TcBackpack.hs +++ b/compiler/typecheck/TcBackpack.hs @@ -549,6 +549,11 @@ checkImplements impl_mod (IndefModule uid mod_name) = do (gresFromAvails Nothing (mi_exports impl_iface)) nsubst = mkNameShape (moduleName impl_mod) (mi_exports impl_iface) + -- Load all the orphans, so the subsequent 'checkHsigIface' sees + -- all the instances it needs to + loadModuleInterfaces (text "Loading orphan modules (from implementor of hsig)") + (dep_orphs (mi_deps impl_iface)) + dflags <- getDynFlags let avails = calculateAvails dflags impl_iface False{- safe -} False{- boot -} diff --git a/testsuite/tests/backpack/should_compile/all.T b/testsuite/tests/backpack/should_compile/all.T index 1f0136f..bb77278 100644 --- a/testsuite/tests/backpack/should_compile/all.T +++ b/testsuite/tests/backpack/should_compile/all.T @@ -33,3 +33,4 @@ test('bkp38', normal, backpack_compile, ['']) test('bkp39', normal, backpack_compile, ['']) test('bkp40', normal, backpack_compile, ['']) test('bkp41', normal, backpack_compile, ['']) +test('bkp42', normal, backpack_compile, ['']) diff --git a/testsuite/tests/backpack/should_compile/bkp41.bkp b/testsuite/tests/backpack/should_compile/bkp42.bkp similarity index 66% copy from testsuite/tests/backpack/should_compile/bkp41.bkp copy to testsuite/tests/backpack/should_compile/bkp42.bkp index e8b5b24..59590f9 100644 --- a/testsuite/tests/backpack/should_compile/bkp41.bkp +++ b/testsuite/tests/backpack/should_compile/bkp42.bkp @@ -5,14 +5,17 @@ unit impl where import A instance Show T where show T = "T" + module C(module B) where + import B unit sig where signature B where - data T = T + data T instance Show T module App where import B - app = print T + app :: T -> IO () + app t = print t unit main where - dependency sig[B=impl:B] + dependency sig[B=impl:C] diff --git a/testsuite/tests/backpack/should_compile/bkp42.stderr b/testsuite/tests/backpack/should_compile/bkp42.stderr new file mode 100644 index 0000000..69d8d7c --- /dev/null +++ b/testsuite/tests/backpack/should_compile/bkp42.stderr @@ -0,0 +1,14 @@ +[1 of 3] Processing impl + Instantiating impl + [1 of 3] Compiling A ( impl/A.hs, bkp42.out/impl/A.o ) + [2 of 3] Compiling B ( impl/B.hs, bkp42.out/impl/B.o ) + [3 of 3] Compiling C ( impl/C.hs, bkp42.out/impl/C.o ) +[2 of 3] Processing sig + [1 of 2] Compiling B[sig] ( sig/B.hsig, nothing ) + [2 of 2] Compiling App ( sig/App.hs, nothing ) +[3 of 3] Processing main + Instantiating main + [1 of 1] Including sig[B=impl:C] + Instantiating sig[B=impl:C] + [1 of 2] Compiling B[sig] ( sig/B.hsig, bkp42.out/sig/sig-Ko6MwJiRFc509cOdDShPV5/B.o ) + [2 of 2] Compiling App ( sig/App.hs, bkp42.out/sig/sig-Ko6MwJiRFc509cOdDShPV5/App.o ) From git at git.haskell.org Wed Dec 14 18:09:47 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Dec 2016 18:09:47 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Revert "Install toplevel handler inside fork." (d864200) Message-ID: <20161214180947.1B9253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/d86420021ffd35e8f09216364d65bd1d18581731/ghc >--------------------------------------------------------------- commit d86420021ffd35e8f09216364d65bd1d18581731 Author: Ben Gamari Date: Tue Dec 13 15:56:44 2016 -0500 Revert "Install toplevel handler inside fork." The test associated with this has given us too much trouble. It's not worth the pain for a minor release. This reverts commit fb0f4cf66f3fc7590821e6688440bf86c25aced1. >--------------------------------------------------------------- d86420021ffd35e8f09216364d65bd1d18581731 includes/RtsAPI.h | 4 ---- rts/Prelude.h | 2 -- rts/RtsAPI.c | 29 ----------------------------- rts/RtsSymbols.c | 1 - rts/Schedule.c | 5 +---- rts/package.conf.in | 2 -- testsuite/tests/rts/T12903.hs | 10 ---------- testsuite/tests/rts/T12903.stdout | 1 - testsuite/tests/rts/all.T | 2 -- 9 files changed, 1 insertion(+), 55 deletions(-) diff --git a/includes/RtsAPI.h b/includes/RtsAPI.h index 0e29c63..4748060 100644 --- a/includes/RtsAPI.h +++ b/includes/RtsAPI.h @@ -245,10 +245,6 @@ void rts_evalIO (/* inout */ Capability **, /* in */ HaskellObj p, /* out */ HaskellObj *ret); -void rts_evalStableIOMain (/* inout */ Capability **, - /* in */ HsStablePtr s, - /* out */ HsStablePtr *ret); - void rts_evalStableIO (/* inout */ Capability **, /* in */ HsStablePtr s, /* out */ HsStablePtr *ret); diff --git a/rts/Prelude.h b/rts/Prelude.h index 444aa46..ae1e9cb 100644 --- a/rts/Prelude.h +++ b/rts/Prelude.h @@ -51,7 +51,6 @@ PRELUDE_CLOSURE(base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure); PRELUDE_CLOSURE(base_GHCziConcziSignal_runHandlersPtr_closure); PRELUDE_CLOSURE(base_GHCziTopHandler_flushStdHandles_closure); -PRELUDE_CLOSURE(base_GHCziTopHandler_runMainIO_closure); PRELUDE_INFO(ghczmprim_GHCziTypes_Czh_static_info); PRELUDE_INFO(ghczmprim_GHCziTypes_Izh_static_info); @@ -100,7 +99,6 @@ PRELUDE_INFO(base_GHCziStable_StablePtr_con_info); #define runHandlersPtr_closure DLL_IMPORT_DATA_REF(base_GHCziConcziSignal_runHandlersPtr_closure) #define flushStdHandles_closure DLL_IMPORT_DATA_REF(base_GHCziTopHandler_flushStdHandles_closure) -#define runMainIO_closure DLL_IMPORT_DATA_REF(base_GHCziTopHandler_runMainIO_closure) #define stackOverflow_closure DLL_IMPORT_DATA_REF(base_GHCziIOziException_stackOverflow_closure) #define heapOverflow_closure DLL_IMPORT_DATA_REF(base_GHCziIOziException_heapOverflow_closure) diff --git a/rts/RtsAPI.c b/rts/RtsAPI.c index 47f6c93..c64d8af 100644 --- a/rts/RtsAPI.c +++ b/rts/RtsAPI.c @@ -460,35 +460,6 @@ void rts_evalIO (/* inout */ Capability **cap, } /* - * rts_evalStableIOMain() is suitable for calling main Haskell thread - * stored in (StablePtr (IO a)) it calls rts_evalStableIO but wraps - * function in GHC.TopHandler.runMainIO that installs top_handlers. - * See Trac #12903. - */ -void rts_evalStableIOMain(/* inout */ Capability **cap, - /* in */ HsStablePtr s, - /* out */ HsStablePtr *ret) -{ - StgTSO* tso; - StgClosure *p, *r, *w; - SchedulerStatus stat; - - p = (StgClosure *)deRefStablePtr(s); - w = rts_apply(*cap, &base_GHCziTopHandler_runMainIO_closure, p); - tso = createStrictIOThread(*cap, RtsFlags.GcFlags.initialStkSize, w); - // async exceptions are always blocked by default in the created - // thread. See #1048. - tso->flags |= TSO_BLOCKEX | TSO_INTERRUPTIBLE; - scheduleWaitThread(tso,&r,cap); - stat = rts_getSchedStatus(*cap); - - if (stat == Success && ret != NULL) { - ASSERT(r != NULL); - *ret = getStablePtr((StgPtr)r); - } -} - -/* * rts_evalStableIO() is suitable for calling from Haskell. It * evaluates a value of the form (StablePtr (IO a)), forcing the * action's result to WHNF before returning. The result is returned diff --git a/rts/RtsSymbols.c b/rts/RtsSymbols.c index 44b6591..fec5cfc 100644 --- a/rts/RtsSymbols.c +++ b/rts/RtsSymbols.c @@ -647,7 +647,6 @@ SymI_HasProto(rts_eval) \ SymI_HasProto(rts_evalIO) \ SymI_HasProto(rts_evalLazyIO) \ - SymI_HasProto(rts_evalStableIOMain) \ SymI_HasProto(rts_evalStableIO) \ SymI_HasProto(rts_eval_) \ SymI_HasProto(rts_getBool) \ diff --git a/rts/Schedule.c b/rts/Schedule.c index 33599d0..1f42e42 100644 --- a/rts/Schedule.c +++ b/rts/Schedule.c @@ -2078,10 +2078,7 @@ forkProcess(HsStablePtr *entry ioManagerStartCap(&cap); #endif - // Install toplevel exception handlers, so interruption - // signal will be sent to the main thread. - // See Trac #12903 - rts_evalStableIOMain(&cap, entry, NULL); // run the action + rts_evalStableIO(&cap, entry, NULL); // run the action rts_checkSchedStatus("forkProcess",cap); rts_unlock(cap); diff --git a/rts/package.conf.in b/rts/package.conf.in index e328be7..c0256bb 100644 --- a/rts/package.conf.in +++ b/rts/package.conf.in @@ -106,7 +106,6 @@ ld-options: , "-Wl,-u,_base_GHCziTopHandler_flushStdHandles_closure" , "-Wl,-u,_base_GHCziTopHandler_runIO_closure" , "-Wl,-u,_base_GHCziTopHandler_runNonIO_closure" - , "-Wl,-u,_base_GHCziTopHandler_runMainIO_closure" , "-Wl,-u,_base_GHCziConcziIO_ensureIOManagerIsRunning_closure" , "-Wl,-u,_base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure" , "-Wl,-u,_base_GHCziConcziSync_runSparks_closure" @@ -149,7 +148,6 @@ ld-options: , "-Wl,-u,base_GHCziTopHandler_flushStdHandles_closure" , "-Wl,-u,base_GHCziTopHandler_runIO_closure" , "-Wl,-u,base_GHCziTopHandler_runNonIO_closure" - , "-Wl,-u,base_GHCziTopHandler_runMainIO_closure" , "-Wl,-u,base_GHCziConcziIO_ensureIOManagerIsRunning_closure" , "-Wl,-u,base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure" , "-Wl,-u,base_GHCziConcziSync_runSparks_closure" diff --git a/testsuite/tests/rts/T12903.hs b/testsuite/tests/rts/T12903.hs deleted file mode 100644 index ddaf8b9..0000000 --- a/testsuite/tests/rts/T12903.hs +++ /dev/null @@ -1,10 +0,0 @@ -import Control.Concurrent -import Control.Exception -import System.Posix - -main = do - pid <- forkProcess $ do - handle (\UserInterrupt{} -> putStrLn "caught") - $ threadDelay 2000000 - signalProcess sigINT pid - threadDelay 2000000 diff --git a/testsuite/tests/rts/T12903.stdout b/testsuite/tests/rts/T12903.stdout deleted file mode 100644 index cad99e1..0000000 --- a/testsuite/tests/rts/T12903.stdout +++ /dev/null @@ -1 +0,0 @@ -caught diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index d889276..f7d518c 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -345,5 +345,3 @@ test('T10296b', [only_ways('threaded2')], compile_and_run, ['']) test('T12497', [ unless(opsys('mingw32'), skip) ], run_command, ['$MAKE -s --no-print-directory T12497']) -test('T12903', [ when(opsys('mingw32'), skip)], compile_and_run, ['']) - From git at git.haskell.org Wed Dec 14 18:17:30 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Dec 2016 18:17:30 +0000 (UTC) Subject: [commit: ghc] master: Fix typo in users' guide (26ce99c) Message-ID: <20161214181730.8AF883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/26ce99cc47446eba704c867fbd2d88f31c325805/ghc >--------------------------------------------------------------- commit 26ce99cc47446eba704c867fbd2d88f31c325805 Author: Ryan Scott Date: Wed Dec 14 13:16:40 2016 -0500 Fix typo in users' guide [ci skip] >--------------------------------------------------------------- 26ce99cc47446eba704c867fbd2d88f31c325805 docs/users_guide/8.2.1-notes.rst | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index ea22d4f..2e9033c 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -95,7 +95,7 @@ Compiler to define a synonym of ``T``, you must write:: - data TSyn = (T :: (forall k. k -> Type) -> Type) + type TSyn = (T :: (forall k. k -> Type) -> Type) - The Mingw-w64 toolchain for the Windows version of GHC has been updated. GHC now uses `GCC 6.2.0` and `binutils 2.27`. From git at git.haskell.org Thu Dec 15 09:08:29 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 09:08:29 +0000 (UTC) Subject: [commit: ghc] master: mk/config.mk.in: enable SMP on ARMv7+ (Trac #12981) (52c5e55) Message-ID: <20161215090829.968653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/52c5e55348170f27f5ef1cb010c4c96ab4aa47cc/ghc >--------------------------------------------------------------- commit 52c5e55348170f27f5ef1cb010c4c96ab4aa47cc Author: Sergei Trofimovich Date: Thu Dec 15 09:02:50 2016 +0000 mk/config.mk.in: enable SMP on ARMv7+ (Trac #12981) Before the change result of expression ArchSupportsSMP="$(if $(filter $(ARM_ISA),ARMv5 ARMv6),NO,YES)" to evaluate to ArchSupportsSMP="YES" After the change it's ArchSupportsSMP=YES Thanks to orion for the fix! Fixes Trac #12981 Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 52c5e55348170f27f5ef1cb010c4c96ab4aa47cc mk/config.mk.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index 35c492f..06c12bf 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -187,7 +187,7 @@ HaveLibDL = @HaveLibDL@ # includes/stg/SMP.h ifeq "$(TargetArch_CPP)" "arm" # We don't support load/store barriers pre-ARMv7. See #10433. -ArchSupportsSMP="$(if $(filter $(ARM_ISA),ARMv5 ARMv6),NO,YES)" +ArchSupportsSMP=$(if $(filter $(ARM_ISA),ARMv5 ARMv6),NO,YES) else ArchSupportsSMP=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 sparc powerpc powerpc64 powerpc64le aarch64))) endif From git at git.haskell.org Thu Dec 15 14:55:21 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 14:55:21 +0000 (UTC) Subject: [commit: ghc] tag 'ghc-8.0.2-rc2' created Message-ID: <20161215145521.80A153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New tag : ghc-8.0.2-rc2 Referencing: b5103deea34e26731a9da51b11fee73e02140ab4 From git at git.haskell.org Thu Dec 15 15:43:22 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 15:43:22 +0000 (UTC) Subject: [commit: ghc] master: Build terminfo on iOS. (6370a56) Message-ID: <20161215154322.0D7F23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6370a564f6bc5d0b40cfa080927130a1b2406557/ghc >--------------------------------------------------------------- commit 6370a564f6bc5d0b40cfa080927130a1b2406557 Author: Shea Levy Date: Wed Dec 14 16:46:03 2016 -0500 Build terminfo on iOS. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2830 >--------------------------------------------------------------- 6370a564f6bc5d0b40cfa080927130a1b2406557 ghc.mk | 4 ---- 1 file changed, 4 deletions(-) diff --git a/ghc.mk b/ghc.mk index 139b6d1..a06c4a7 100644 --- a/ghc.mk +++ b/ghc.mk @@ -432,10 +432,8 @@ else # CLEANING PACKAGES_STAGE0 = binary Cabal/Cabal hpc ghc-boot-th ghc-boot hoopl transformers template-haskell ifeq "$(Windows_Host)" "NO" -ifneq "$(HostOS_CPP)" "ios" PACKAGES_STAGE0 += terminfo endif -endif PACKAGES_STAGE1 += ghc-prim PACKAGES_STAGE1 += $(INTEGER_LIBRARY) @@ -472,10 +470,8 @@ PACKAGES_STAGE1 += xhtml endif ifeq "$(Windows_Target)" "NO" -ifneq "$(TargetOS_CPP)" "ios" PACKAGES_STAGE1 += terminfo endif -endif PACKAGES_STAGE1 += haskeline PACKAGES_STAGE1 += ghci From git at git.haskell.org Thu Dec 15 15:43:24 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 15:43:24 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Specify expected allocations of T12877 for Windows (2940a61) Message-ID: <20161215154324.BD5F23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2940a61722b5e5b35421b385dedf07f82c63557d/ghc >--------------------------------------------------------------- commit 2940a61722b5e5b35421b385dedf07f82c63557d Author: Ben Gamari Date: Wed Dec 14 16:51:54 2016 -0500 testsuite: Specify expected allocations of T12877 for Windows This deviated by 12% from the expected allocations on Windows. Yet another case of #12758. >--------------------------------------------------------------- 2940a61722b5e5b35421b385dedf07f82c63557d testsuite/tests/perf/compiler/all.T | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 38cbdd0..ec59805 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -900,8 +900,12 @@ test('T12877', [(wordsize(64), 197582248, 5), # initial: 197582248 (Linux) ]) + , compiler_stats_num_field('bytes allocated', - [(wordsize(64), 135979000, 5), + [(platform('x86_64-unknown-mingw32'), 118644280, 5), + # initial: 118644280 + + (wordsize(64), 135979000, 5), # initial: 135979000 (Linux) ]), ], From git at git.haskell.org Thu Dec 15 15:43:28 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 15:43:28 +0000 (UTC) Subject: [commit: ghc] master: Make unboxedTuple{Type, Data}Name support 0- and 1-tuples (9550b8d) Message-ID: <20161215154328.0B7393A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9550b8d810c3ce9fcf3419da367041124e2673de/ghc >--------------------------------------------------------------- commit 9550b8d810c3ce9fcf3419da367041124e2673de Author: Ryan Scott Date: Wed Dec 14 16:47:53 2016 -0500 Make unboxedTuple{Type,Data}Name support 0- and 1-tuples Previously, these functions were hardcoded so as to always `error` whenever given an argument of 0 or 1. This restriction can be lifted pretty easily, however. This requires a slight tweak to `isBuiltInOcc_maybe` in `TysWiredIn` to allow it to recognize `Unit#` (which is the hard-wired `OccName` for unboxed 1-tuples). Fixes #12977. Test Plan: make test TEST=12977 Reviewers: austin, goldfire, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2847 GHC Trac Issues: #12977 >--------------------------------------------------------------- 9550b8d810c3ce9fcf3419da367041124e2673de compiler/prelude/TysWiredIn.hs | 1 + .../template-haskell/Language/Haskell/TH/Syntax.hs | 19 ++++++++----------- libraries/template-haskell/changelog.md | 3 +++ testsuite/tests/th/T12977.hs | 12 ++++++++++++ testsuite/tests/th/all.T | 1 + 5 files changed, 25 insertions(+), 11 deletions(-) diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index 18cf530..6e028fc 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -691,6 +691,7 @@ isBuiltInOcc_maybe occ = -- unboxed tuple data/tycon "(##)" -> Just $ tup_name Unboxed 0 + "Unit#" -> Just $ tup_name Unboxed 1 _ | Just rest <- "(#" `stripPrefix` name , (commas, rest') <- BS.span (==',') rest , "#)" <- rest' diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 4e21e8b..c9bccf6 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -1187,20 +1187,17 @@ unboxedTupleDataName :: Int -> Name -- | Unboxed tuple type constructor unboxedTupleTypeName :: Int -> Name -unboxedTupleDataName 0 = error "unboxedTupleDataName 0" -unboxedTupleDataName 1 = error "unboxedTupleDataName 1" -unboxedTupleDataName n = mk_unboxed_tup_name (n-1) DataName - -unboxedTupleTypeName 0 = error "unboxedTupleTypeName 0" -unboxedTupleTypeName 1 = error "unboxedTupleTypeName 1" -unboxedTupleTypeName n = mk_unboxed_tup_name (n-1) TcClsName +unboxedTupleDataName n = mk_unboxed_tup_name n DataName +unboxedTupleTypeName n = mk_unboxed_tup_name n TcClsName mk_unboxed_tup_name :: Int -> NameSpace -> Name -mk_unboxed_tup_name n_commas space - = Name occ (NameG space (mkPkgName "ghc-prim") tup_mod) +mk_unboxed_tup_name n space + = Name (mkOccName tup_occ) (NameG space (mkPkgName "ghc-prim") tup_mod) where - occ = mkOccName ("(#" ++ replicate n_commas ',' ++ "#)") - tup_mod = mkModName "GHC.Tuple" + tup_occ | n == 1 = "Unit#" -- See Note [One-tuples] in TysWiredIn + | otherwise = "(#" ++ replicate n_commas ',' ++ "#)" + n_commas = n - 1 + tup_mod = mkModName "GHC.Tuple" ----------------------------------------------------- -- Locations diff --git a/libraries/template-haskell/changelog.md b/libraries/template-haskell/changelog.md index c4b8f03..1f41a6a 100644 --- a/libraries/template-haskell/changelog.md +++ b/libraries/template-haskell/changelog.md @@ -16,6 +16,9 @@ * Add support for attaching deriving strategies to `deriving` statements (#10598) + * `unboxedTupleTypeName` and `unboxedTupleDataName` now work for unboxed + 0-tuples and 1-tuples (#12977) + ## 2.11.0.0 *May 2016* * Bundled with GHC 8.0.1 diff --git a/testsuite/tests/th/T12977.hs b/testsuite/tests/th/T12977.hs new file mode 100644 index 0000000..69832b8 --- /dev/null +++ b/testsuite/tests/th/T12977.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE UnboxedTuples #-} +module T12977 where + +import Language.Haskell.TH.Lib +import Language.Haskell.TH.Syntax + +zero :: () -> $(conT (unboxedTupleTypeName 0)) +zero () = $(conE (unboxedTupleDataName 0)) + +one :: () -> $(conT (unboxedTupleTypeName 1) `appT` conT ''Int) +one () = $(conE (unboxedTupleDataName 1)) 42 diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index b144419..c2c9fa2 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -444,3 +444,4 @@ test('T12646', normal, compile, ['-v0']) test('T12788', extra_clean(['T12788_Lib.hi', 'T12788_Lib.o']), multimod_compile_fail, ['T12788.hs', '-v0 ' + config.ghc_th_way_flags]) +test('T12977', normal, compile, ['-v0']) From git at git.haskell.org Thu Dec 15 15:43:32 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 15:43:32 +0000 (UTC) Subject: [commit: ghc] master: Show constraints when reporting typed holes (0c3341b) Message-ID: <20161215154332.17FBB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0c3341b23e0672fb9c05d9f6ab0be76f411d526e/ghc >--------------------------------------------------------------- commit 0c3341b23e0672fb9c05d9f6ab0be76f411d526e Author: Maciej Bielecki Date: Wed Dec 14 16:43:25 2016 -0500 Show constraints when reporting typed holes This patch implements the display of constraints in the error message for typed holes. Test Plan: validate, read docs Reviewers: simonpj, austin, bgamari Reviewed By: simonpj, bgamari Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D2767 GHC Trac Issues: #10614 >--------------------------------------------------------------- 0c3341b23e0672fb9c05d9f6ab0be76f411d526e compiler/main/DynFlags.hs | 4 +- compiler/typecheck/TcErrors.hs | 45 +++++++++++++++- docs/users_guide/glasgow_exts.rst | 27 ++++++++++ testsuite/tests/typecheck/should_compile/all.T | 2 + .../typecheck/should_compile/hole_constraints.hs | 27 ++++++++++ .../should_compile/hole_constraints.stderr | 61 ++++++++++++++++++++++ .../should_compile/hole_constraints_nested.hs | 12 +++++ .../should_compile/hole_constraints_nested.stderr | 15 ++++++ utils/mkUserGuidePart/Options/Verbosity.hs | 4 ++ 9 files changed, 195 insertions(+), 2 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0c3341b23e0672fb9c05d9f6ab0be76f411d526e From git at git.haskell.org Thu Dec 15 15:43:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 15:43:34 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Mark T9577 as broken due to #12965 (be5384c) Message-ID: <20161215154334.C98593A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/be5384cea2b89791a9334c4eaa313edcc4055042/ghc >--------------------------------------------------------------- commit be5384cea2b89791a9334c4eaa313edcc4055042 Author: Ben Gamari Date: Wed Dec 14 16:46:46 2016 -0500 testsuite: Mark T9577 as broken due to #12965 Test Plan: validate Reviewers: austin, Phyx Reviewed By: Phyx Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2835 GHC Trac Issues: #12965 >--------------------------------------------------------------- be5384cea2b89791a9334c4eaa313edcc4055042 testsuite/tests/codeGen/should_run/all.T | 1 + 1 file changed, 1 insertion(+) diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index cd212c3..3b02579 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -150,4 +150,5 @@ test('T12757', normal, compile_and_run, ['']) test('T12855', normal, compile_and_run, ['']) test('T9577', [ unless(arch('x86_64') or arch('i386'),skip), when(opsys('darwin'), expect_broken(12937)), + when(opsys('mingw32'), expect_broken(12965)), only_ways(['normal']) ], compile_and_run, ['']) From git at git.haskell.org Thu Dec 15 15:43:37 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 15:43:37 +0000 (UTC) Subject: [commit: ghc] master: Add entry to .gitignore to for __.SYMDEF_SORTED (fe5d68a) Message-ID: <20161215154337.856653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fe5d68ad1ae5faaaf786f334edf251295195ef6d/ghc >--------------------------------------------------------------- commit fe5d68ad1ae5faaaf786f334edf251295195ef6d Author: John Leo Date: Wed Dec 14 16:47:18 2016 -0500 Add entry to .gitignore to for __.SYMDEF_SORTED libraries/integer-gmp/gmp/objs/__.SYMDEF SORTED is created by Mac OS builds. Test Plan: validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2840 >--------------------------------------------------------------- fe5d68ad1ae5faaaf786f334edf251295195ef6d .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index f58d782..270fd37 100644 --- a/.gitignore +++ b/.gitignore @@ -32,6 +32,7 @@ foo* *.dyn_o *.dyn_hi __pycache__ +*.SYMDEF* log tags From git at git.haskell.org Thu Dec 15 15:43:40 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 15:43:40 +0000 (UTC) Subject: [commit: ghc] master: check-ppr: Add a --dump flag to aid in debugging (5c76f83) Message-ID: <20161215154340.587383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5c76f834b5b7f2ee9712d0888a8b1b186b77dee5/ghc >--------------------------------------------------------------- commit 5c76f834b5b7f2ee9712d0888a8b1b186b77dee5 Author: Ben Gamari Date: Wed Dec 14 17:09:02 2016 -0500 check-ppr: Add a --dump flag to aid in debugging Currently tracking down where two ASTs disagree is quite difficult. Add a --dump flag to check-ppr which dumps the respective ASTs to files, which can then be easily compared with diff, etc. >--------------------------------------------------------------- 5c76f834b5b7f2ee9712d0888a8b1b186b77dee5 utils/check-ppr/Main.hs | 26 +++++++++++++++++++++----- utils/check-ppr/README | 3 +++ 2 files changed, 24 insertions(+), 5 deletions(-) diff --git a/utils/check-ppr/Main.hs b/utils/check-ppr/Main.hs index c61b0e6..8c93769 100644 --- a/utils/check-ppr/Main.hs +++ b/utils/check-ppr/Main.hs @@ -1,6 +1,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE RankNTypes #-} +import Control.Monad (when) import Data.Data hiding (Fixity) import Data.List import Bag @@ -20,15 +21,27 @@ import System.FilePath import qualified Data.ByteString as B import qualified Data.Map as Map -main::IO() +usage :: String +usage = unlines + [ "usage: check-ppr [--dump] (libdir) (file)" + , "" + , "where libdir is the GHC library directory (e.g. the output of" + , "ghc --print-libdir) and file is the file to parse." + , "The --dump flag causes check-ppr to produce .new and .old files" + , "containing dumps of the new and old ASTs in the event of a match" + , "failure." + ] + +main :: IO() main = do args <- getArgs case args of - [libdir,fileName] -> testOneFile libdir fileName - _ -> putStrLn "invoke with the libdir and a file to parse." + [libdir,fileName] -> testOneFile libdir fileName False + ["--dump", libdir,fileName] -> testOneFile libdir fileName True + _ -> putStrLn usage -testOneFile :: FilePath -> String -> IO () -testOneFile libdir fileName = do +testOneFile :: FilePath -> String -> Bool -> IO () +testOneFile libdir fileName dumpOldNew = do p <- parseOneFile libdir fileName let origAst = showAstData 0 (pm_parsed_source p) @@ -56,6 +69,9 @@ testOneFile libdir fileName = do putStrLn origAst putStrLn "\n===================================\nNew\n\n" putStrLn newAstStr + when dumpOldNew $ do + writeFile (fileName <.> "old") origAst + writeFile (fileName <.> "new") newAstStr exitFailure diff --git a/utils/check-ppr/README b/utils/check-ppr/README index ac0eb55..d31442a 100644 --- a/utils/check-ppr/README +++ b/utils/check-ppr/README @@ -18,3 +18,6 @@ In a test Makefile $(CHECK_PPR) "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" FileToParse.hs See examples in (REPO_HOME)/testsuite/tests/printer/Makefile + +If passed the --dump flag check-ppr will produce .new and .old files containing +the ASTs before and after round-tripping to aid debugging. From git at git.haskell.org Thu Dec 15 15:43:43 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 15:43:43 +0000 (UTC) Subject: [commit: ghc] master: Fix pprCLabel on platforms without native codegen. (3c7cf18) Message-ID: <20161215154343.54E163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3c7cf18c5ed8cb20c37732258db616d8858619a7/ghc >--------------------------------------------------------------- commit 3c7cf18c5ed8cb20c37732258db616d8858619a7 Author: Shea Levy Date: Wed Dec 14 16:46:27 2016 -0500 Fix pprCLabel on platforms without native codegen. D1290 added a panic in a code path that can be reached when !cGhcWithNativeCodeGen. This reverts just that part of that patch. Reviewers: austin, simonmar, bgamari, xnyhps Reviewed By: simonmar Subscribers: xnyhps, thomie Differential Revision: https://phabricator.haskell.org/D2831 >--------------------------------------------------------------- 3c7cf18c5ed8cb20c37732258db616d8858619a7 compiler/cmm/CLabel.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs index 7317ea4..3fd081c 100644 --- a/compiler/cmm/CLabel.hs +++ b/compiler/cmm/CLabel.hs @@ -1113,8 +1113,8 @@ pprAsmCLbl _ lbl = pprCLbl lbl pprCLbl :: CLabel -> SDoc -pprCLbl (StringLitLabel _) - = panic "pprCLbl StringLitLabel" +pprCLbl (StringLitLabel u) + = pprUnique u <> text "_str" pprCLbl (CaseLabel u CaseReturnPt) = hcat [pprUnique u, text "_ret"] From git at git.haskell.org Thu Dec 15 15:43:46 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 15:43:46 +0000 (UTC) Subject: [commit: ghc] master: procPointAnalysis doesn't need UniqSM (27287c8) Message-ID: <20161215154346.073C13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/27287c802010ddf4f5d633de6b61b40a50a38c64/ghc >--------------------------------------------------------------- commit 27287c802010ddf4f5d633de6b61b40a50a38c64 Author: Michal Terepeta Date: Wed Dec 14 16:47:05 2016 -0500 procPointAnalysis doesn't need UniqSM `procPointAnalysis` doesn't need to run in `UniqSM` (it consists of a single `return` and the call to `analyzeCmm` function which is pure). Making it non-monadic simplifies the code a bit. Signed-off-by: Michal Terepeta Test Plan: validate Reviewers: austin, bgamari, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2837 >--------------------------------------------------------------- 27287c802010ddf4f5d633de6b61b40a50a38c64 compiler/cmm/CmmPipeline.hs | 4 +-- compiler/cmm/CmmProcPoint.hs | 58 ++++++++++++++++++++------------------------ 2 files changed, 28 insertions(+), 34 deletions(-) diff --git a/compiler/cmm/CmmPipeline.hs b/compiler/cmm/CmmPipeline.hs index b19e418..a0fe4b1 100644 --- a/compiler/cmm/CmmPipeline.hs +++ b/compiler/cmm/CmmPipeline.hs @@ -109,8 +109,8 @@ cpsTop hsc_env proc = g <- if splitting_proc_points then do ------------- Split into separate procedures ----------------------- - pp_map <- {-# SCC "procPointAnalysis" #-} runUniqSM $ - procPointAnalysis proc_points g + let pp_map = {-# SCC "procPointAnalysis" #-} + procPointAnalysis proc_points g dumpWith dflags Opt_D_dump_cmm_procmap "procpoint map" $ ppr pp_map g <- {-# SCC "splitAtProcPoints" #-} runUniqSM $ diff --git a/compiler/cmm/CmmProcPoint.hs b/compiler/cmm/CmmProcPoint.hs index 608654f..3dc7ac4 100644 --- a/compiler/cmm/CmmProcPoint.hs +++ b/compiler/cmm/CmmProcPoint.hs @@ -131,10 +131,9 @@ instance Outputable Status where -- Once you know what the proc-points are, figure out -- what proc-points each block is reachable from -- See Note [Proc-point analysis] -procPointAnalysis :: ProcPointSet -> CmmGraph -> UniqSM (LabelMap Status) +procPointAnalysis :: ProcPointSet -> CmmGraph -> LabelMap Status procPointAnalysis procPoints cmmGraph@(CmmGraph {g_graph = graph}) = - return $ - analyzeCmmFwd procPointLattice procPointTransfer cmmGraph initProcPoints + analyzeCmmFwd procPointLattice procPointTransfer cmmGraph initProcPoints where initProcPoints = mkFactBase @@ -189,36 +188,31 @@ minimalProcPointSet :: Platform -> ProcPointSet -> CmmGraph minimalProcPointSet platform callProcPoints g = extendPPSet platform g (postorderDfs g) callProcPoints -extendPPSet :: Platform -> CmmGraph -> [CmmBlock] -> ProcPointSet -> UniqSM ProcPointSet +extendPPSet + :: Platform -> CmmGraph -> [CmmBlock] -> ProcPointSet -> UniqSM ProcPointSet extendPPSet platform g blocks procPoints = - do env <- procPointAnalysis procPoints g - -- pprTrace "extensPPSet" (ppr env) $ return () - let add block pps = let id = entryLabel block - in case mapLookup id env of - Just ProcPoint -> setInsert id pps - _ -> pps - procPoints' = foldGraphBlocks add setEmpty g - newPoints = mapMaybe ppSuccessor blocks - newPoint = listToMaybe newPoints - ppSuccessor b = - let nreached id = case mapLookup id env `orElse` - pprPanic "no ppt" (ppr id <+> ppr b) of - ProcPoint -> 1 - ReachedBy ps -> setSize ps - block_procpoints = nreached (entryLabel b) - -- | Looking for a successor of b that is reached by - -- more proc points than b and is not already a proc - -- point. If found, it can become a proc point. - newId succ_id = not (setMember succ_id procPoints') && - nreached succ_id > block_procpoints - in listToMaybe $ filter newId $ successors b -{- - case newPoints of - [] -> return procPoints' - pps -> extendPPSet g blocks - (foldl extendBlockSet procPoints' pps) --} - case newPoint of + let env = procPointAnalysis procPoints g + add block pps = let id = entryLabel block + in case mapLookup id env of + Just ProcPoint -> setInsert id pps + _ -> pps + procPoints' = foldGraphBlocks add setEmpty g + newPoints = mapMaybe ppSuccessor blocks + newPoint = listToMaybe newPoints + ppSuccessor b = + let nreached id = case mapLookup id env `orElse` + pprPanic "no ppt" (ppr id <+> ppr b) of + ProcPoint -> 1 + ReachedBy ps -> setSize ps + block_procpoints = nreached (entryLabel b) + -- | Looking for a successor of b that is reached by + -- more proc points than b and is not already a proc + -- point. If found, it can become a proc point. + newId succ_id = not (setMember succ_id procPoints') && + nreached succ_id > block_procpoints + in listToMaybe $ filter newId $ successors b + + in case newPoint of Just id -> if setMember id procPoints' then panic "added old proc pt" From git at git.haskell.org Thu Dec 15 15:43:49 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 15:43:49 +0000 (UTC) Subject: [commit: ghc] master: Adds llvm-prof flavour (8b2e588) Message-ID: <20161215154349.529353A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8b2e5881550be049303b99d7862fb3c85b9ae2a4/ghc >--------------------------------------------------------------- commit 8b2e5881550be049303b99d7862fb3c85b9ae2a4 Author: Moritz Angermann Date: Wed Dec 14 16:45:48 2016 -0500 Adds llvm-prof flavour Reviewers: austin, bgamari, RyanGlScott Reviewed By: bgamari, RyanGlScott Subscribers: RyanGlScott, thomie Differential Revision: https://phabricator.haskell.org/D2824 >--------------------------------------------------------------- 8b2e5881550be049303b99d7862fb3c85b9ae2a4 mk/build.mk.sample | 3 +++ mk/flavours/{prof.mk => prof-llvm.mk} | 2 +- 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/mk/build.mk.sample b/mk/build.mk.sample index 6266219..e9219bd 100644 --- a/mk/build.mk.sample +++ b/mk/build.mk.sample @@ -34,6 +34,9 @@ # Profile the stage2 compiler: #BuildFlavour = prof +# Profile the stage2 compiler (LLVM backend): +#BuildFlavour = prof-llvm + # A development build, working on the stage 1 compiler: #BuildFlavour = devel1 diff --git a/mk/flavours/prof.mk b/mk/flavours/prof-llvm.mk similarity index 86% copy from mk/flavours/prof.mk copy to mk/flavours/prof-llvm.mk index 67f89e6..b54fabd 100644 --- a/mk/flavours/prof.mk +++ b/mk/flavours/prof-llvm.mk @@ -1,4 +1,4 @@ -SRC_HC_OPTS = -O0 -H64m +SRC_HC_OPTS = -O0 -H64m -fllvm GhcStage1HcOpts = -O GhcStage2HcOpts = -O GhcLibHcOpts = -O From git at git.haskell.org Thu Dec 15 15:43:52 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 15:43:52 +0000 (UTC) Subject: [commit: ghc] master: Reset FPU precision back to MSVCRT defaults (6f7d827) Message-ID: <20161215154352.E60543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6f7d8279cea4aa1082fb07adf5da507297e21ee8/ghc >--------------------------------------------------------------- commit 6f7d8279cea4aa1082fb07adf5da507297e21ee8 Author: Tamar Christina Date: Wed Dec 14 16:45:35 2016 -0500 Reset FPU precision back to MSVCRT defaults Mingw-w64 does a stupid thing. They set the FPU precision to extended mode by default. The reasoning is that it's for compatibility with GNU Linux ported libraries. However the problem is this is incompatible with the standard Windows double precision mode. In fact, if we create a new OS thread then Windows will reset the FPU to double precision mode. So we end up with a weird state where the main thread by default has a different precision than any child threads. Test Plan: ./validate new test T7289 Reviewers: simonmar, austin, bgamari, erikd Reviewed By: simonmar Subscribers: thomie, #ghc_windows_task_force Differential Revision: https://phabricator.haskell.org/D2819 GHC Trac Issues: #7289 >--------------------------------------------------------------- 6f7d8279cea4aa1082fb07adf5da507297e21ee8 rts/RtsStartup.c | 34 +++++++++++++++++++--- .../should_compile => rts/T7289}/Makefile | 0 testsuite/tests/rts/T7289/T7289.hs | 9 ++++++ testsuite/tests/rts/T7289/T7289.stdout | 2 ++ testsuite/tests/rts/T7289/all.T | 6 ++++ testsuite/tests/rts/T7289/fp.c | 26 +++++++++++++++++ 6 files changed, 73 insertions(+), 4 deletions(-) diff --git a/rts/RtsStartup.c b/rts/RtsStartup.c index dd4efa6..955ad13 100644 --- a/rts/RtsStartup.c +++ b/rts/RtsStartup.c @@ -46,7 +46,9 @@ #include "win32/AsyncIO.h" #endif -#if !defined(mingw32_HOST_OS) +#if defined(mingw32_HOST_OS) +#include +#else #include "posix/TTY.h" #endif @@ -69,10 +71,18 @@ static void flushStdHandles(void); #define X86_INIT_FPU 0 -#if X86_INIT_FPU static void x86_init_fpu ( void ) { +#if defined(mingw32_HOST_OS) && !X86_INIT_FPU + /* Mingw-w64 does a stupid thing. They set the FPU precision to extended mode by default. + The reasoning is that it's for compatibility with GNU Linux ported libraries. However the + problem is this is incompatible with the standard Windows double precision mode. In fact, + if we create a new OS thread then Windows will reset the FPU to double precision mode. + So we end up with a weird state where the main thread by default has a different precision + than any child threads. */ + fesetenv(FE_PC53_ENV); +#elif X86_INIT_FPU __volatile unsigned short int fpu_cw; // Grab the control word @@ -87,8 +97,26 @@ x86_init_fpu ( void ) // Store the new control word back __asm __volatile ("fldcw %0" : : "m" (fpu_cw)); +#else + return; +#endif +} + +#if defined(mingw32_HOST_OS) +/* And now we have to override the build in ones in Mingw-W64's CRT. */ +void _fpreset(void) +{ + x86_init_fpu(); +} + +#ifdef __GNUC__ +void __attribute__((alias("_fpreset"))) fpreset(void); +#else +void fpreset(void) { + _fpreset(); } #endif +#endif /* ----------------------------------------------------------------------------- Starting up the RTS @@ -244,9 +272,7 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config) startupAsyncIO(); #endif -#if X86_INIT_FPU x86_init_fpu(); -#endif startupHpc(); diff --git a/testsuite/tests/annotations/should_compile/Makefile b/testsuite/tests/rts/T7289/Makefile similarity index 100% copy from testsuite/tests/annotations/should_compile/Makefile copy to testsuite/tests/rts/T7289/Makefile diff --git a/testsuite/tests/rts/T7289/T7289.hs b/testsuite/tests/rts/T7289/T7289.hs new file mode 100644 index 0000000..1751333 --- /dev/null +++ b/testsuite/tests/rts/T7289/T7289.hs @@ -0,0 +1,9 @@ +module Main where + +import Control.Concurrent + +foreign import ccall "showControlBits" checkfpu :: IO () + +main + = do checkfpu + forkOS checkfpu diff --git a/testsuite/tests/rts/T7289/T7289.stdout b/testsuite/tests/rts/T7289/T7289.stdout new file mode 100644 index 0000000..7a74a81 --- /dev/null +++ b/testsuite/tests/rts/T7289/T7289.stdout @@ -0,0 +1,2 @@ +FPU: 0x027f +FPU: 0x027f diff --git a/testsuite/tests/rts/T7289/all.T b/testsuite/tests/rts/T7289/all.T new file mode 100644 index 0000000..7ef59cc --- /dev/null +++ b/testsuite/tests/rts/T7289/all.T @@ -0,0 +1,6 @@ +test('T7289', [ extra_clean(['fp.o', 'testfp.o', 'testfp.hi']) + , extra_files(['fp.c']) + , unless(opsys('mingw32'), skip) + , only_ways(['threaded1']) + ], + compile_and_run, ['fp.c']) diff --git a/testsuite/tests/rts/T7289/fp.c b/testsuite/tests/rts/T7289/fp.c new file mode 100644 index 0000000..12f1b39 --- /dev/null +++ b/testsuite/tests/rts/T7289/fp.c @@ -0,0 +1,26 @@ +#include +#include +#include + +static unsigned int +getFPUStateX86 (void) +{ + unsigned int control = 0; +#if defined(_MSC_VER) + control = _controlfp(0, 0); +#else + __asm__ __volatile__("fnstcw %0" : "=m" (control)); +#endif + return control; +} + +static unsigned int +getSSEStateX86 (void) +{ + return _mm_getcsr(); +} + +extern void showControlBits (void) +{ + printf("FPU: 0x%04x\n", getFPUStateX86()); +} From git at git.haskell.org Thu Dec 15 18:07:44 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 18:07:44 +0000 (UTC) Subject: [commit: ghc] master: Fix cost-centre-stacks bug (#5654) (394231b) Message-ID: <20161215180744.C7CF33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/394231b301efb6b56654b0a480ab794fe3b7e4db/ghc >--------------------------------------------------------------- commit 394231b301efb6b56654b0a480ab794fe3b7e4db Author: Simon Marlow Date: Thu Dec 15 11:17:19 2016 -0500 Fix cost-centre-stacks bug (#5654) This fixes some cases of wrong stacks being generated by the profiler. For background and details on the fix see `Note [Evaluating functions with profiling]` in `rts/Apply.cmm`. This does have an impact on allocations for some programs when profiling. nofib results: ``` k-nucleotide +0.0% +8.8% +11.0% +11.0% 0.0% puzzle +0.0% +12.5% 0.244 0.246 0.0% typecheck 0.0% +8.7% +16.1% +16.2% 0.0% ------------------------------------------------------------------------ -------- Min -0.0% -0.0% -34.4% -35.5% -25.0% Max +0.0% +12.5% +48.9% +49.4% +10.6% Geometric Mean +0.0% +0.6% +2.0% +1.8% -0.3% ``` But runtimes don't seem to be affected much, and the examples I looked at were completely legitimate. For example, in puzzle we have this: ``` position :: ItemType -> StateType -> BankType position Bono = bonoPos position Edge = edgePos position Larry = larryPos position Adam = adamPos ``` where the identifiers on the rhs are all record selectors. Previously the profiler gave a stack that looked like ``` position bonoPos ... ``` i.e. `bonoPos` was at the same level of the call stack as `position`, but now it looks like ``` position bonoPos ... ``` I used the normaliser from the testsuite to diff the profiling output from other nofib programs and they all looked better. Test Plan: * the broken test passes * validate * compiled and ran all of nofib, measured perf, diff'd several .prof files Reviewers: niteria, erikd, austin, scpmw, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2804 GHC Trac Issues: #5654, #10007 >--------------------------------------------------------------- 394231b301efb6b56654b0a480ab794fe3b7e4db compiler/codeGen/StgCmmClosure.hs | 6 +- includes/Cmm.h | 6 ++ rts/Apply.cmm | 107 +++++++++++++++++++++ .../profiling/should_run/{T5654.hs => T5654-O0.hs} | 0 .../profiling/should_run/T5654-O0.prof.sample | 28 ++++++ .../profiling/should_run/{T5654.hs => T5654-O1.hs} | 0 .../profiling/should_run/T5654-O1.prof.sample | 27 ++++++ .../tests/profiling/should_run/T5654.prof.sample | 28 ------ .../tests/profiling/should_run/T680.prof.sample | 50 +++++----- testsuite/tests/profiling/should_run/all.T | 4 +- 10 files changed, 200 insertions(+), 56 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 394231b301efb6b56654b0a480ab794fe3b7e4db From git at git.haskell.org Thu Dec 15 18:07:47 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 18:07:47 +0000 (UTC) Subject: [commit: ghc] master: Fix pretty printing of MINIMAL signatures (1ec632f) Message-ID: <20161215180747.AD8193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1ec632f880ab730f99ae9286d5be8e2287330ca4/ghc >--------------------------------------------------------------- commit 1ec632f880ab730f99ae9286d5be8e2287330ca4 Author: Matthew Pickering Date: Thu Dec 15 11:17:34 2016 -0500 Fix pretty printing of MINIMAL signatures Reviewers: austin, alanz, bgamari Reviewed By: alanz, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2836 >--------------------------------------------------------------- 1ec632f880ab730f99ae9286d5be8e2287330ca4 compiler/hsSyn/HsBinds.hs | 5 +++-- testsuite/tests/printer/Ppr023.hs | 4 ++++ 2 files changed, 7 insertions(+), 2 deletions(-) diff --git a/compiler/hsSyn/HsBinds.hs b/compiler/hsSyn/HsBinds.hs index 5933df8..421a358 100644 --- a/compiler/hsSyn/HsBinds.hs +++ b/compiler/hsSyn/HsBinds.hs @@ -972,7 +972,8 @@ ppr_sig (InlineSig var inl) <+> pprPrefixOcc (unLoc var)) ppr_sig (SpecInstSig src ty) = pragSrcBrackets src "{-# SPECIALISE" (text "instance" <+> ppr ty) -ppr_sig (MinimalSig _ bf) = pragBrackets (pprMinimalSig bf) +ppr_sig (MinimalSig src bf) + = pragSrcBrackets src "{-# MINIMAL" (pprMinimalSig bf) ppr_sig (PatSynSig names sig_ty) = text "pattern" <+> pprVarSig (map unLoc names) (ppr sig_ty) ppr_sig (SCCFunSig src fn mlabel) @@ -1013,7 +1014,7 @@ instance Outputable TcSpecPrag where pprMinimalSig :: (OutputableBndr name) => LBooleanFormula (Located name) -> SDoc -pprMinimalSig (L _ bf) = text "MINIMAL" <+> ppr (fmap unLoc bf) +pprMinimalSig (L _ bf) = ppr (fmap unLoc bf) {- ************************************************************************ diff --git a/testsuite/tests/printer/Ppr023.hs b/testsuite/tests/printer/Ppr023.hs index 7291854..32cb9bb 100644 --- a/testsuite/tests/printer/Ppr023.hs +++ b/testsuite/tests/printer/Ppr023.hs @@ -35,3 +35,7 @@ class Foo a where baz :: a -> a -> Bool quux :: a -> a -> Bool {-# MINIMAL bar, (foo, baq | foo, quux) #-} + +class Foo2 a where + f :: a + {-# MiNiMaL f #-} From git at git.haskell.org Thu Dec 15 18:07:50 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 18:07:50 +0000 (UTC) Subject: [commit: ghc] master: Warn about missing instance methods that start with an underscore (503219e) Message-ID: <20161215180750.74C123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/503219e3e1667ac39607021b2d9586260fbab32b/ghc >--------------------------------------------------------------- commit 503219e3e1667ac39607021b2d9586260fbab32b Author: Ryan Scott Date: Thu Dec 15 11:17:49 2016 -0500 Warn about missing instance methods that start with an underscore Previously, GHC would not warn whenever there was a class instance that didn't implement a class method whose name begins with an underscore. Fixes #12959. Test Plan: make test TEST=WarnMinimal Reviewers: austin, bgamari, simonpj Reviewed By: bgamari, simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2849 GHC Trac Issues: #12959 >--------------------------------------------------------------- 503219e3e1667ac39607021b2d9586260fbab32b compiler/typecheck/TcClassDcl.hs | 6 ++---- docs/users_guide/8.2.1-notes.rst | 12 ++++++++++++ testsuite/tests/warnings/minimal/WarnMinimal.hs | 4 ++-- testsuite/tests/warnings/minimal/WarnMinimal.stderr | 8 +++++++- 4 files changed, 23 insertions(+), 7 deletions(-) diff --git a/compiler/typecheck/TcClassDcl.hs b/compiler/typecheck/TcClassDcl.hs index 162e91a..c5a4c3a 100644 --- a/compiler/typecheck/TcClassDcl.hs +++ b/compiler/typecheck/TcClassDcl.hs @@ -293,12 +293,10 @@ tcClassMinimalDef _clas sigs op_info (\bf -> addWarnTc NoReason (warningMinimalDefIncomplete bf)) return mindef where - -- By default require all methods without a default - -- implementation whose names don't start with '_' + -- By default require all methods without a default implementation defMindef :: ClassMinimalDef defMindef = mkAnd [ noLoc (mkVar name) - | (name, _, Nothing) <- op_info - , not (startsWithUnderscore (getOccName name)) ] + | (name, _, Nothing) <- op_info ] instantiateMethod :: Class -> Id -> [TcType] -> TcType -- Take a class operation, say diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index 2e9033c..3011a29 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -100,6 +100,18 @@ Compiler - The Mingw-w64 toolchain for the Windows version of GHC has been updated. GHC now uses `GCC 6.2.0` and `binutils 2.27`. +- Previously, :ghc-flag:`-Wmissing-methods` would not warn whenever a type + class method beginning with an underscore was not implemented in an instance. + For instance, this code would compile without any warnings: :: + + class Foo a where + _Bar :: a -> Int + + instance Foo Int + + :ghc-flag:`-Wmissing-methods` will now warn that ``_Bar`` is not implemented + in the ``Foo Int`` instance. + GHCi ~~~~ diff --git a/testsuite/tests/warnings/minimal/WarnMinimal.hs b/testsuite/tests/warnings/minimal/WarnMinimal.hs index d369065..d6c9b7b 100644 --- a/testsuite/tests/warnings/minimal/WarnMinimal.hs +++ b/testsuite/tests/warnings/minimal/WarnMinimal.hs @@ -87,7 +87,7 @@ class Cheater a where -- WARNING LINE class Cheater2 a where _cheater2 :: a - {-# MINIMAL #-} -- no warning + {-# MINIMAL #-} -- warning! class Cheater3 a where -- WARNING LINE cheater3, cheater3b :: a @@ -100,7 +100,7 @@ instance Num Bool where -- WARNING LINE class NoExplicit a where needed :: a - _optional :: a + _alsoNeeded :: a instance NoExplicit Int where -- WARNING LINE diff --git a/testsuite/tests/warnings/minimal/WarnMinimal.stderr b/testsuite/tests/warnings/minimal/WarnMinimal.stderr index d907a6c..4323a91 100644 --- a/testsuite/tests/warnings/minimal/WarnMinimal.stderr +++ b/testsuite/tests/warnings/minimal/WarnMinimal.stderr @@ -30,6 +30,12 @@ WarnMinimal.hs:84:1: warning: but there is no default implementation. • In the class declaration for ‘Cheater’ +WarnMinimal.hs:88:1: warning: + • The MINIMAL pragma does not require: + ‘_cheater2’ + but there is no default implementation. + • In the class declaration for ‘Cheater2’ + WarnMinimal.hs:92:1: warning: • The MINIMAL pragma does not require: ‘cheater3b’ @@ -45,7 +51,7 @@ WarnMinimal.hs:99:10: warning: [-Wmissing-methods (in -Wdefault)] WarnMinimal.hs:105:10: warning: [-Wmissing-methods (in -Wdefault)] • No explicit implementation for - ‘needed’ + ‘needed’ and ‘_alsoNeeded’ • In the instance declaration for ‘NoExplicit Int’ WarnMinimal.hs:116:10: warning: [-Wmissing-methods (in -Wdefault)] From git at git.haskell.org Thu Dec 15 18:07:53 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 18:07:53 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Separate out Windows results for T5205 (d398162) Message-ID: <20161215180753.435F43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d39816285341cf639b51ae14f65c63a3e89bba95/ghc >--------------------------------------------------------------- commit d39816285341cf639b51ae14f65c63a3e89bba95 Author: Ben Gamari Date: Thu Dec 15 11:18:05 2016 -0500 testsuite: Separate out Windows results for T5205 This test seems to have much different allocation behavior on Windows and Linux. Previously we had widened the acceptance window to 7% to accomodate this, but even this isn't enough any more. Instead of further widening the window let's just give an expected number for each platform. Really, this is precisely the issue with our performance testing model which I've been complaining about in #12758. Fixes test for #5205 on 64-bit Windows. Test Plan: Validate on Windows Reviewers: austin Subscribers: thomie, Phyx Differential Revision: https://phabricator.haskell.org/D2848 GHC Trac Issues: #5205 >--------------------------------------------------------------- d39816285341cf639b51ae14f65c63a3e89bba95 testsuite/tests/perf/should_run/all.T | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/should_run/all.T b/testsuite/tests/perf/should_run/all.T index da75f42..5e7e5cf 100644 --- a/testsuite/tests/perf/should_run/all.T +++ b/testsuite/tests/perf/should_run/all.T @@ -191,12 +191,17 @@ test('T5205', [stats_num_field('bytes allocated', [(wordsize(32), 47088, 5), # expected value: 47088 (x86/Darwin) - (wordsize(64), 56208, 7)]), + + (platform('x86_64-unknown-mingw32'), 52264, 5), + # 2016-12-14: 52264 (Separate out Windows results) + + (wordsize(64), 56208, 5)]), # expected value: 51320 (amd64/Linux) # 2014-07-17: 52600 (amd64/Linux) general round of updates # 2015-04-03: Widen 5->7% (amd64/Windows was doing better) # 2015-08-15: 50648 (Windows too good. avg of Windows&Linux) # 2015-10-30: 56208 (D757: Emit Typeable at definition site) + # 2016-12-14: Narrow 7->5% (Separate out Windows results) only_ways(['normal', 'optasm']) ], compile_and_run, From git at git.haskell.org Thu Dec 15 19:51:47 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 19:51:47 +0000 (UTC) Subject: [commit: packages/terminfo] master: Define missing Semigroup instance (19500c7) Message-ID: <20161215195147.793F43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/terminfo On branch : master Link : http://git.haskell.org/packages/terminfo.git/commitdiff/19500c702f87680a5f143331286bd4755912ec05 >--------------------------------------------------------------- commit 19500c702f87680a5f143331286bd4755912ec05 Author: Herbert Valerio Riedel Date: Fri Jan 1 10:05:03 2016 +0100 Define missing Semigroup instance This makes `terminfo` `-Wcompat`-clean. >--------------------------------------------------------------- 19500c702f87680a5f143331286bd4755912ec05 System/Console/Terminfo/Base.hs | 13 ++++++++++++- 1 file changed, 12 insertions(+), 1 deletion(-) diff --git a/System/Console/Terminfo/Base.hs b/System/Console/Terminfo/Base.hs index d2b262c..a0042eb 100644 --- a/System/Console/Terminfo/Base.hs +++ b/System/Console/Terminfo/Base.hs @@ -45,7 +45,9 @@ module System.Console.Terminfo.Base( import Control.Applicative import Control.Monad -#if !MIN_VERSION_base(4,8,0) +#if MIN_VERSION_base(4,9,0) +import Data.Semigroup +#elif !MIN_VERSION_base(4,8,0) import Data.Monoid #endif import Foreign.C @@ -140,9 +142,18 @@ newtype TermOutput = TermOutput ([TermOutputType] -> [TermOutputType]) data TermOutputType = TOCmd LinesAffected String | TOStr String +#if MIN_VERSION_base(4,9,0) +instance Semigroup TermOutput where + TermOutput xs <> TermOutput ys = TermOutput (xs . ys) + +instance Monoid TermOutput where + mempty = TermOutput id + mappend = (<>) +#else instance Monoid TermOutput where mempty = TermOutput id TermOutput xs `mappend` TermOutput ys = TermOutput (xs . ys) +#endif termText :: String -> TermOutput termText str = TermOutput (TOStr str :) From git at git.haskell.org Thu Dec 15 19:51:49 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 19:51:49 +0000 (UTC) Subject: [commit: packages/terminfo] master: Merge pull request #13 from hvr/pr/semigroup (d879cf5) Message-ID: <20161215195149.7C9263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/terminfo On branch : master Link : http://git.haskell.org/packages/terminfo.git/commitdiff/d879cf56dbaf9a536a5927ac15caef27dbfb807f >--------------------------------------------------------------- commit d879cf56dbaf9a536a5927ac15caef27dbfb807f Merge: 140ca44 19500c7 Author: Judah Jacobson Date: Fri Jan 1 15:25:15 2016 -0800 Merge pull request #13 from hvr/pr/semigroup Define missing Semigroup instance >--------------------------------------------------------------- d879cf56dbaf9a536a5927ac15caef27dbfb807f System/Console/Terminfo/Base.hs | 13 ++++++++++++- 1 file changed, 12 insertions(+), 1 deletion(-) From git at git.haskell.org Thu Dec 15 19:51:51 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 19:51:51 +0000 (UTC) Subject: [commit: packages/terminfo] master: Bump upper bound on base (6ab1dff) Message-ID: <20161215195151.81DCE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/terminfo On branch : master Link : http://git.haskell.org/packages/terminfo.git/commitdiff/6ab1dffebc0665dd347eba351a495dd80032d0e5 >--------------------------------------------------------------- commit 6ab1dffebc0665dd347eba351a495dd80032d0e5 Author: Ben Gamari Date: Tue Nov 15 14:31:27 2016 -0500 Bump upper bound on base >--------------------------------------------------------------- 6ab1dffebc0665dd347eba351a495dd80032d0e5 terminfo.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/terminfo.cabal b/terminfo.cabal index 2dfbee9..745aa12 100644 --- a/terminfo.cabal +++ b/terminfo.cabal @@ -29,7 +29,7 @@ Library other-extensions: CPP, DeriveDataTypeable, FlexibleInstances, ScopedTypeVariables if impl(ghc>=7.3) other-extensions: Safe, Trustworthy - build-depends: base >= 4.3 && < 4.10 + build-depends: base >= 4.3 && < 4.11 ghc-options: -Wall exposed-modules: System.Console.Terminfo From git at git.haskell.org Thu Dec 15 19:54:17 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 19:54:17 +0000 (UTC) Subject: [commit: ghc] master: base: Bump version to 4.10.0.0 (4d683fa) Message-ID: <20161215195417.21E7D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4d683fa11a5140b74f588b93f93f7891f79ac891/ghc >--------------------------------------------------------------- commit 4d683fa11a5140b74f588b93f93f7891f79ac891 Author: Ben Gamari Date: Tue Nov 15 10:26:14 2016 -0500 base: Bump version to 4.10.0.0 Updates a number of submodules. >--------------------------------------------------------------- 4d683fa11a5140b74f588b93f93f7891f79ac891 compiler/ghc.cabal.in | 2 +- ghc/ghc-bin.cabal.in | 2 +- libraries/Cabal | 2 +- libraries/array | 2 +- libraries/base/base.cabal | 2 +- libraries/compact/compact.cabal | 2 +- libraries/deepseq | 2 +- libraries/directory | 2 +- libraries/filepath | 2 +- libraries/ghc-boot-th/ghc-boot-th.cabal.in | 2 +- libraries/ghc-boot/ghc-boot.cabal.in | 4 ++-- libraries/ghci/ghci.cabal.in | 2 +- libraries/haskeline | 2 +- libraries/hoopl | 2 +- libraries/hpc | 2 +- libraries/parallel | 2 +- libraries/process | 2 +- libraries/stm | 2 +- libraries/template-haskell/template-haskell.cabal | 2 +- libraries/terminfo | 2 +- libraries/unix | 2 +- testsuite/tests/ado/ado004.stderr | 2 +- testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stdout | 4 ++-- testsuite/tests/backpack/should_compile/bkp16.stderr | 4 ++-- testsuite/tests/backpack/should_fail/bkpfail16.stderr | 4 ++-- testsuite/tests/backpack/should_fail/bkpfail17.stderr | 4 ++-- testsuite/tests/backpack/should_fail/bkpfail19.stderr | 4 ++-- testsuite/tests/cabal/cabal09/reexport.cabal | 2 +- testsuite/tests/determinism/determ021/determ021.stdout | 4 ++-- testsuite/tests/ghci/scripts/ghci008.stdout | 4 ++-- testsuite/tests/indexed-types/should_compile/T3017.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ADT.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr1.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/AddAndOr2.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/AddAndOr3.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/AddAndOr4.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/AddAndOr5.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/AddAndOr6.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/BoolToBool.stderr | 4 ++-- .../partial-sigs/should_compile/DataFamilyInstanceLHS.stderr | 2 +- .../tests/partial-sigs/should_compile/Defaulting1MROn.stderr | 4 ++-- .../tests/partial-sigs/should_compile/Defaulting2MROff.stderr | 2 +- .../tests/partial-sigs/should_compile/Defaulting2MROn.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Either.stderr | 2 +- .../tests/partial-sigs/should_compile/EqualityConstraint.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Every.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/EveryNamed.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ExpressionSig.stderr | 4 ++-- .../tests/partial-sigs/should_compile/ExpressionSigNamed.stderr | 4 ++-- .../tests/partial-sigs/should_compile/ExtraConstraints1.stderr | 2 +- .../tests/partial-sigs/should_compile/ExtraConstraints2.stderr | 4 ++-- .../tests/partial-sigs/should_compile/ExtraConstraints3.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROff.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROn.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Forall1.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/GenNamed.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/HigherRank1.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/HigherRank2.stderr | 4 ++-- .../tests/partial-sigs/should_compile/LocalDefinitionBug.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/Meltdown.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/MonoLocalBinds.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/NamedTyVar.stderr | 2 +- .../should_compile/NamedWildcardInDataFamilyInstanceLHS.stderr | 2 +- .../should_compile/NamedWildcardInTypeFamilyInstanceLHS.stderr | 2 +- .../tests/partial-sigs/should_compile/ParensAroundContext.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/PatBind.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/PatBind2.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/PatternSig.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/Recursive.stderr | 4 ++-- .../tests/partial-sigs/should_compile/ScopedNamedWildcards.stderr | 4 ++-- .../partial-sigs/should_compile/ScopedNamedWildcardsGood.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/ShowNamed.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/SimpleGen.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/SkipMany.stderr | 2 +- .../tests/partial-sigs/should_compile/SomethingShowable.stderr | 2 +- .../partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Uncurry.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/UncurryNamed.stderr | 2 +- .../should_compile/WarningWildcardInstantiations.stderr | 2 +- testsuite/tests/plugins/annotation-plugin/annotation-plugin.cabal | 2 +- testsuite/tests/rename/should_fail/rnfail040.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles1.stderr | 2 +- testsuite/tests/roles/should_compile/Roles14.stderr | 2 +- testsuite/tests/roles/should_compile/Roles2.stderr | 2 +- testsuite/tests/roles/should_compile/Roles3.stderr | 2 +- testsuite/tests/roles/should_compile/Roles4.stderr | 2 +- testsuite/tests/roles/should_compile/T8958.stderr | 2 +- testsuite/tests/safeHaskell/check/Check01.stderr | 2 +- testsuite/tests/safeHaskell/check/Check06.stderr | 2 +- testsuite/tests/safeHaskell/check/Check08.stderr | 2 +- testsuite/tests/safeHaskell/check/Check09.stderr | 8 ++++---- testsuite/tests/safeHaskell/check/pkg01/ImpSafe01.stderr | 4 ++-- testsuite/tests/safeHaskell/check/pkg01/ImpSafe04.stderr | 4 ++-- testsuite/tests/safeHaskell/flags/SafeFlags17.stderr | 4 ++-- testsuite/tests/typecheck/should_compile/T12763.stderr | 2 +- testsuite/tests/typecheck/should_compile/tc231.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail182.stderr | 2 +- utils/ghc-cabal/ghc-cabal.cabal | 2 +- utils/ghc-pkg/ghc-pkg.cabal | 2 +- utils/haddock | 2 +- utils/hpc/hpc-bin.cabal | 2 +- utils/hsc2hs | 2 +- utils/runghc/runghc.cabal.in | 2 +- 103 files changed, 143 insertions(+), 143 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4d683fa11a5140b74f588b93f93f7891f79ac891 From git at git.haskell.org Thu Dec 15 23:17:28 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 23:17:28 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add test for #12971 (8f0546b) Message-ID: <20161215231728.C57F23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8f0546bfaf47ec865bb0c6dc2cb0ac451367f65a/ghc >--------------------------------------------------------------- commit 8f0546bfaf47ec865bb0c6dc2cb0ac451367f65a Author: Ben Gamari Date: Thu Dec 15 15:26:11 2016 -0500 testsuite: Add test for #12971 Test Plan: Validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2855 GHC Trac Issues: #12971 >--------------------------------------------------------------- 8f0546bfaf47ec865bb0c6dc2cb0ac451367f65a testsuite/tests/driver/Makefile | 5 +++++ testsuite/tests/driver/T12971.hs | 4 ++++ testsuite/tests/driver/all.T | 2 ++ 3 files changed, 11 insertions(+) diff --git a/testsuite/tests/driver/Makefile b/testsuite/tests/driver/Makefile index 2dfb41f..d3f78ef 100644 --- a/testsuite/tests/driver/Makefile +++ b/testsuite/tests/driver/Makefile @@ -641,3 +641,8 @@ T10923: T12955: ! "$(TEST_HC)" $(TEST_HC_OPTS) --make T12955 ! "$(TEST_HC)" $(TEST_HC_OPTS) --make T12955 -fbuilding-cabal-package + +.PHONY: T12971 +T12971: + mkdir -p ä + ! TMP=ä "$(TEST_HC)" $(TEST_HC_OPTS) --make T12971 diff --git a/testsuite/tests/driver/T12971.hs b/testsuite/tests/driver/T12971.hs new file mode 100644 index 0000000..7b83609 --- /dev/null +++ b/testsuite/tests/driver/T12971.hs @@ -0,0 +1,4 @@ +-- Test that setting the TMP environment variable to a path with non-ASCII +-- characters works. +main :: IO () +main = putStrLn "hello world" diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T index 9119c71..d327ac5 100644 --- a/testsuite/tests/driver/all.T +++ b/testsuite/tests/driver/all.T @@ -501,3 +501,5 @@ test('T10923', test('T12752pass', normal, compile, ['-DSHOULD_PASS=1 -Wcpp-undef']) test('T12955', normal, run_command, ['$MAKE -s --no-print-directory T12955']) + +test('T12971', expect_broken(12971), run_command, ['$MAKE -s --no-print-directory T12971']) \ No newline at end of file From git at git.haskell.org Thu Dec 15 23:17:31 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 23:17:31 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Mark T10294 as fixed (0cad52d) Message-ID: <20161215231731.841763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0cad52d6395487b617edef2b131909d3b4085be4/ghc >--------------------------------------------------------------- commit 0cad52d6395487b617edef2b131909d3b4085be4 Author: Ben Gamari Date: Thu Dec 15 15:26:39 2016 -0500 testsuite: Mark T10294 as fixed It seems that c3c702441137dc8f7ee0dd5ac313be96d625459a resolved #10301. It took a while to notice this since it only broke when tested against a statically linked GHC, a configuration which Harbormaster doesn't test. Test Plan: Validate Reviewers: angerman, austin Subscribers: thomie, nomeata Differential Revision: https://phabricator.haskell.org/D2856 GHC Trac Issues: #10294, #10301 >--------------------------------------------------------------- 0cad52d6395487b617edef2b131909d3b4085be4 testsuite/tests/plugins/all.T | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/testsuite/tests/plugins/all.T b/testsuite/tests/plugins/all.T index cca03bc..26f377c 100644 --- a/testsuite/tests/plugins/all.T +++ b/testsuite/tests/plugins/all.T @@ -48,8 +48,7 @@ test('T10420', test('T10294', [pre_cmd('$MAKE -s --no-print-directory -C annotation-plugin package.T10294 TOP={top}'), - clean_cmd('$MAKE -s --no-print-directory -C annotation-plugin clean.T10294'), - unless(have_dynamic(),expect_broken(10301))], + clean_cmd('$MAKE -s --no-print-directory -C annotation-plugin clean.T10294')], run_command, ['$MAKE -s --no-print-directory T10294']) From git at git.haskell.org Thu Dec 15 23:17:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 23:17:34 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add test for #12966 (81c4956) Message-ID: <20161215231734.E2DCC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/81c49562570a403e8470f73f4decd3e0cb891983/ghc >--------------------------------------------------------------- commit 81c49562570a403e8470f73f4decd3e0cb891983 Author: Ben Gamari Date: Thu Dec 15 15:27:01 2016 -0500 testsuite: Add test for #12966 This isn't exactly a typechecker test, but it was the most appropriate directory I could think of. The issue being tested is fixed. Test Plan: Validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2857 GHC Trac Issues: #12966 >--------------------------------------------------------------- 81c49562570a403e8470f73f4decd3e0cb891983 testsuite/tests/typecheck/should_fail/T12966.hs | 4 ++++ testsuite/tests/typecheck/should_fail/T12966.stderr | 6 ++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 11 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T12966.hs b/testsuite/tests/typecheck/should_fail/T12966.hs new file mode 100644 index 0000000..27bcff6 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T12966.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE RankNTypes #-} +module T12966 where +-- This should fail with a proper error message, not a compiler panic. +type Maybeify c = forall d. (c d) => ((~) (Maybe d)) diff --git a/testsuite/tests/typecheck/should_fail/T12966.stderr b/testsuite/tests/typecheck/should_fail/T12966.stderr new file mode 100644 index 0000000..dd63bf4 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T12966.stderr @@ -0,0 +1,6 @@ + +T12966.hs:4:39: error: + • Expecting one more argument to ‘(~) (Maybe d)’ + Expected a type, but ‘(~) (Maybe d)’ has kind ‘* -> Constraint’ + • In the type ‘forall d. (c d) => ((~) (Maybe d))’ + In the type declaration for ‘Maybeify’ diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 6f99a94..9f578a0 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -432,3 +432,4 @@ test('T12529', normal, compile_fail, ['']) test('T12729', normal, compile_fail, ['']) test('T12803', normal, compile_fail, ['']) test('T12042', extra_clean(['T12042a.hi', 'T12042a.o', 'T12042.hi-boot', 'T12042.o-boot']), multimod_compile_fail, ['T12042', '']) +test('T12966', normal, compile_fail, ['']) \ No newline at end of file From git at git.haskell.org Thu Dec 15 23:50:38 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 23:50:38 +0000 (UTC) Subject: [commit: packages/array] master: Update changelog and bump version to 0.5.1.2 (b8a8d09) Message-ID: <20161215235038.42FB53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array On branch : master Link : http://git.haskell.org/packages/array.git/commitdiff/b8a8d09ddc20a9c9d99bd03b136718b543edb877 >--------------------------------------------------------------- commit b8a8d09ddc20a9c9d99bd03b136718b543edb877 Author: Ben Gamari Date: Thu Dec 15 15:29:16 2016 -0500 Update changelog and bump version to 0.5.1.2 >--------------------------------------------------------------- b8a8d09ddc20a9c9d99bd03b136718b543edb877 array.cabal | 2 +- changelog.md | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/array.cabal b/array.cabal index 91343e1..f52e562 100644 --- a/array.cabal +++ b/array.cabal @@ -1,5 +1,5 @@ name: array -version: 0.5.1.1 +version: 0.5.1.2 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE diff --git a/changelog.md b/changelog.md index a0c41eb..8421c23 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,10 @@ # Changelog for [`array` package](http://hackage.haskell.org/package/array) +## 0.5.1.2 *TBD* + + * Bundled with GHC 8.2.1 + * Overflow check in `unsafeNewArray` + ## 0.5.1.1 *Apr 2016* * Bundled with GHC 8.0.1 From git at git.haskell.org Thu Dec 15 23:50:40 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 23:50:40 +0000 (UTC) Subject: [commit: packages/array] master: Data.Array.Base: Check for overflow in size calculations (cb2446d) Message-ID: <20161215235040.4962F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array On branch : master Link : http://git.haskell.org/packages/array.git/commitdiff/cb2446dfeafd63a9013be43689a66a499a7f0862 >--------------------------------------------------------------- commit cb2446dfeafd63a9013be43689a66a499a7f0862 Author: Ben Gamari Date: Tue Dec 6 20:38:59 2016 -0500 Data.Array.Base: Check for overflow in size calculations Fixes GHC #4505. >--------------------------------------------------------------- cb2446dfeafd63a9013be43689a66a499a7f0862 Data/Array/Base.hs | 44 ++++++++++++++++++++++++++++++-------------- tests/T229.hs | 9 +++++++++ tests/T229.stderr | 3 +++ tests/all.T | 2 +- 4 files changed, 43 insertions(+), 15 deletions(-) diff --git a/Data/Array/Base.hs b/Data/Array/Base.hs index 9908ad2..c88e272 100644 --- a/Data/Array/Base.hs +++ b/Data/Array/Base.hs @@ -1065,7 +1065,7 @@ instance MArray (STUArray s) Char (ST s) where {-# INLINE getNumElements #-} getNumElements (STUArray _ _ n _) = return n {-# INLINE unsafeNewArray_ #-} - unsafeNewArray_ (l,u) = unsafeNewArraySTUArray_ (l,u) (*# 4#) + unsafeNewArray_ (l,u) = unsafeNewArraySTUArray_ (l,u) (safe_scale 4#) {-# INLINE newArray_ #-} newArray_ arrBounds = newArray arrBounds (chr 0) {-# INLINE unsafeRead #-} @@ -1227,7 +1227,7 @@ instance MArray (STUArray s) Int16 (ST s) where {-# INLINE getNumElements #-} getNumElements (STUArray _ _ n _) = return n {-# INLINE unsafeNewArray_ #-} - unsafeNewArray_ (l,u) = unsafeNewArraySTUArray_ (l,u) (*# 2#) + unsafeNewArray_ (l,u) = unsafeNewArraySTUArray_ (l,u) (safe_scale 2#) {-# INLINE newArray_ #-} newArray_ arrBounds = newArray arrBounds 0 {-# INLINE unsafeRead #-} @@ -1245,7 +1245,7 @@ instance MArray (STUArray s) Int32 (ST s) where {-# INLINE getNumElements #-} getNumElements (STUArray _ _ n _) = return n {-# INLINE unsafeNewArray_ #-} - unsafeNewArray_ (l,u) = unsafeNewArraySTUArray_ (l,u) (*# 4#) + unsafeNewArray_ (l,u) = unsafeNewArraySTUArray_ (l,u) (safe_scale 4#) {-# INLINE newArray_ #-} newArray_ arrBounds = newArray arrBounds 0 {-# INLINE unsafeRead #-} @@ -1263,7 +1263,7 @@ instance MArray (STUArray s) Int64 (ST s) where {-# INLINE getNumElements #-} getNumElements (STUArray _ _ n _) = return n {-# INLINE unsafeNewArray_ #-} - unsafeNewArray_ (l,u) = unsafeNewArraySTUArray_ (l,u) (*# 8#) + unsafeNewArray_ (l,u) = unsafeNewArraySTUArray_ (l,u) (safe_scale 8#) {-# INLINE newArray_ #-} newArray_ arrBounds = newArray arrBounds 0 {-# INLINE unsafeRead #-} @@ -1299,7 +1299,7 @@ instance MArray (STUArray s) Word16 (ST s) where {-# INLINE getNumElements #-} getNumElements (STUArray _ _ n _) = return n {-# INLINE unsafeNewArray_ #-} - unsafeNewArray_ (l,u) = unsafeNewArraySTUArray_ (l,u) (*# 2#) + unsafeNewArray_ (l,u) = unsafeNewArraySTUArray_ (l,u) (safe_scale 2#) {-# INLINE newArray_ #-} newArray_ arrBounds = newArray arrBounds 0 {-# INLINE unsafeRead #-} @@ -1317,7 +1317,7 @@ instance MArray (STUArray s) Word32 (ST s) where {-# INLINE getNumElements #-} getNumElements (STUArray _ _ n _) = return n {-# INLINE unsafeNewArray_ #-} - unsafeNewArray_ (l,u) = unsafeNewArraySTUArray_ (l,u) (*# 4#) + unsafeNewArray_ (l,u) = unsafeNewArraySTUArray_ (l,u) (safe_scale 4#) {-# INLINE newArray_ #-} newArray_ arrBounds = newArray arrBounds 0 {-# INLINE unsafeRead #-} @@ -1335,7 +1335,7 @@ instance MArray (STUArray s) Word64 (ST s) where {-# INLINE getNumElements #-} getNumElements (STUArray _ _ n _) = return n {-# INLINE unsafeNewArray_ #-} - unsafeNewArray_ (l,u) = unsafeNewArraySTUArray_ (l,u) (*# 8#) + unsafeNewArray_ (l,u) = unsafeNewArraySTUArray_ (l,u) (safe_scale 8#) {-# INLINE newArray_ #-} newArray_ arrBounds = newArray arrBounds 0 {-# INLINE unsafeRead #-} @@ -1352,13 +1352,29 @@ instance MArray (STUArray s) Word64 (ST s) where bOOL_SCALE, bOOL_WORD_SCALE, wORD_SCALE, dOUBLE_SCALE, fLOAT_SCALE :: Int# -> Int# -bOOL_SCALE n# = (n# +# last#) `uncheckedIShiftRA#` 3# - where !(I# last#) = SIZEOF_HSWORD * 8 - 1 -bOOL_WORD_SCALE n# = bOOL_INDEX (n# +# last#) - where !(I# last#) = SIZEOF_HSWORD * 8 - 1 -wORD_SCALE n# = scale# *# n# where !(I# scale#) = SIZEOF_HSWORD -dOUBLE_SCALE n# = scale# *# n# where !(I# scale#) = SIZEOF_HSDOUBLE -fLOAT_SCALE n# = scale# *# n# where !(I# scale#) = SIZEOF_HSFLOAT +bOOL_SCALE n# + | isTrue# (res# ># n#) = res# + | otherwise = error "Data.Array.Base.bOOL_SCALE: Overflow" + where + !(I# last#) = SIZEOF_HSWORD * 8 - 1 + !res# = (n# +# last#) `uncheckedIShiftRA#` 3# +bOOL_WORD_SCALE n# + | isTrue# (res# ># n#) = res# + | otherwise = error "Data.Array.Base.bOOL_WORD_SCALE: Overflow" + where + !(I# last#) = SIZEOF_HSWORD * 8 - 1 + !res# = bOOL_INDEX (n# +# last#) +wORD_SCALE n# = safe_scale scale# n# where !(I# scale#) = SIZEOF_HSWORD +dOUBLE_SCALE n# = safe_scale scale# n# where !(I# scale#) = SIZEOF_HSDOUBLE +fLOAT_SCALE n# = safe_scale scale# n# where !(I# scale#) = SIZEOF_HSFLOAT + +safe_scale :: Int# -> Int# -> Int# +safe_scale scale# n# + | isTrue# (res# >=# n#) = res# + | otherwise = error "Data.Array.Base.safe_scale: Overflow" + where + !res# = scale# *# n# + bOOL_INDEX :: Int# -> Int# #if SIZEOF_HSWORD == 4 diff --git a/tests/T229.hs b/tests/T229.hs new file mode 100644 index 0000000..2265852 --- /dev/null +++ b/tests/T229.hs @@ -0,0 +1,9 @@ +import Data.Array.MArray +import Data.Array.IO +import Data.Word + +main :: IO () +main = do + -- This should fail due to integer overflow + m <- newArray_ (0,2^62-1) :: IO (IOUArray Int Word32) -- allocates 0 bytes + readArray m 17 >>= print -- Read some random location in address space diff --git a/tests/T229.stderr b/tests/T229.stderr new file mode 100644 index 0000000..deb6094 --- /dev/null +++ b/tests/T229.stderr @@ -0,0 +1,3 @@ +T229: Data.Array.Base.safe_scale: Overflow +CallStack (from HasCallStack): + error, called at libraries/array/Data/Array/Base.hs:1374:17 in array-0.5.1.2:Data.Array.Base diff --git a/tests/all.T b/tests/all.T index 4fd4844..a5f92e7 100644 --- a/tests/all.T +++ b/tests/all.T @@ -1,4 +1,3 @@ - test('T2120', normal, compile_and_run, ['']) test('largeArray', normal, compile_and_run, ['']) test('array001', [ @@ -7,3 +6,4 @@ test('array001', [ compile_and_run, ['']) test('T9220', normal, ghci_script, ['T9220.script']) +test('T229', [exit_code(1)], compile_and_run, ['']) From git at git.haskell.org Thu Dec 15 23:52:14 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Dec 2016 23:52:14 +0000 (UTC) Subject: [commit: ghc] master: array: Check for integer overflow during allocation (cd4b202) Message-ID: <20161215235214.AD97E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cd4b202f24da928adf66c05443b457002ab6a3e1/ghc >--------------------------------------------------------------- commit cd4b202f24da928adf66c05443b457002ab6a3e1 Author: Ben Gamari Date: Thu Dec 15 17:47:08 2016 -0500 array: Check for integer overflow during allocation This fixes #229, where creating a new array can cause array to allocate a smaller array than it thinks it allocates due to integer overflow, resulting in memory unsafety. This breaks the rts/overflow1 test, which relied on this unchecked overflow. I fix it by reimplementing the test in terms of newByteArray# directly. Updates the array submodule. >--------------------------------------------------------------- cd4b202f24da928adf66c05443b457002ab6a3e1 libraries/array | 2 +- testsuite/tests/rts/overflow1.hs | 20 +++++++++++++++----- 2 files changed, 16 insertions(+), 6 deletions(-) diff --git a/libraries/array b/libraries/array index bab2c23..b8a8d09 160000 --- a/libraries/array +++ b/libraries/array @@ -1 +1 @@ -Subproject commit bab2c234f176fe3e95443cbe4387833da22f7e5d +Subproject commit b8a8d09ddc20a9c9d99bd03b136718b543edb877 diff --git a/testsuite/tests/rts/overflow1.hs b/testsuite/tests/rts/overflow1.hs index 63ed5a4..74a396b 100644 --- a/testsuite/tests/rts/overflow1.hs +++ b/testsuite/tests/rts/overflow1.hs @@ -1,11 +1,21 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE UnboxedTuples #-} + module Main where -import Data.Array.IO -import Data.Word +import GHC.Exts +import GHC.Base -- Try to overflow BLOCK_ROUND_UP in the computation of req_blocks in allocate() --- Here we invoke allocate() via newByteArray# and the array package. +-- Here we invoke allocate() via newByteArray#. -- Request a number of bytes close to HS_WORD_MAX, -- subtracting a few words for overhead in newByteArray#. --- Allocate Word32s (rather than Word8s) to get around bounds-checking in array. -main = newArray (0,maxBound `div` 4 - 10) 0 :: IO (IOUArray Word Word32) +main :: IO () +main = + IO $ \s1# -> + case newByteArray# (maxInt# -# 10#) s1# of + (# s2#, _ #) -> (# s2#, () #) + where + maxInt# :: Int# + !(I# maxInt#) = maxBound From git at git.haskell.org Fri Dec 16 00:56:19 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Dec 2016 00:56:19 +0000 (UTC) Subject: [commit: ghc] master: UniqSupply: Use full range of machine word (0d213c1) Message-ID: <20161216005619.090E13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0d213c18b6962bb65e2b3035a258dd3f5bf454dd/ghc >--------------------------------------------------------------- commit 0d213c18b6962bb65e2b3035a258dd3f5bf454dd Author: Ben Gamari Date: Thu Dec 15 18:57:26 2016 -0500 UniqSupply: Use full range of machine word Currently uniques are 32-bits wide. 8 of these bits are for the unique class, leaving only 24 for the unique number itself. This seems dangerously small for a large project. Let's use the full range of the native machine word. We also add (now largely unnecessary) overflow check to ensure that the unique number doesn't overflow. Test Plan: Validate Reviewers: simonmar, austin, niteria Reviewed By: niteria Subscribers: mpickering, thomie Differential Revision: https://phabricator.haskell.org/D2844 GHC Trac Issues: #12944 >--------------------------------------------------------------- 0d213c18b6962bb65e2b3035a258dd3f5bf454dd compiler/Unique.h | 3 +++ compiler/basicTypes/UniqSupply.hs | 6 ++++-- compiler/basicTypes/Unique.hs | 15 +++++++++++---- compiler/cbits/genSym.c | 25 +++++++++++++++++++++---- 4 files changed, 39 insertions(+), 10 deletions(-) diff --git a/compiler/Unique.h b/compiler/Unique.h new file mode 100644 index 0000000..a786d8f --- /dev/null +++ b/compiler/Unique.h @@ -0,0 +1,3 @@ +#include "../includes/MachDeps.h" + +#define UNIQUE_BITS (WORD_SIZE_IN_BITS - 8) diff --git a/compiler/basicTypes/UniqSupply.hs b/compiler/basicTypes/UniqSupply.hs index 9f97d49..431c96c 100644 --- a/compiler/basicTypes/UniqSupply.hs +++ b/compiler/basicTypes/UniqSupply.hs @@ -3,7 +3,7 @@ (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 -} -{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE CPP, UnboxedTuples #-} module UniqSupply ( -- * Main data type @@ -38,6 +38,8 @@ import Control.Monad import Data.Bits import Data.Char +#include "Unique.h" + {- ************************************************************************ * * @@ -75,7 +77,7 @@ takeUniqFromSupply :: UniqSupply -> (Unique, UniqSupply) -- ^ Obtain the 'Unique' from this particular 'UniqSupply', and a new supply mkSplitUniqSupply c - = case ord c `shiftL` 24 of + = case ord c `shiftL` UNIQUE_BITS of mask -> let -- here comes THE MAGIC: diff --git a/compiler/basicTypes/Unique.hs b/compiler/basicTypes/Unique.hs index e24d56b..a6ac670 100644 --- a/compiler/basicTypes/Unique.hs +++ b/compiler/basicTypes/Unique.hs @@ -8,6 +8,7 @@ comparison key in the compiler. If there is any single operation that needs to be fast, it is @Unique@ + comparison. Unsurprisingly, there is quite a bit of huff-and-puff directed to that end. @@ -63,6 +64,7 @@ module Unique ( ) where #include "HsVersions.h" +#include "Unique.h" import BasicTypes import FastString @@ -126,6 +128,11 @@ deriveUnique (MkUnique i) delta = mkUnique 'X' (i + delta) -- newTagUnique changes the "domain" of a unique to a different char newTagUnique u c = mkUnique c i where (_,i) = unpkUnique u +-- | How many bits are devoted to the unique index (as opposed to the class +-- character). +uniqueMask :: Int +uniqueMask = (1 `shiftL` UNIQUE_BITS) - 1 + -- pop the Char in the top 8 bits of the Unique(Supply) -- No 64-bit bugs here, as long as we have at least 32 bits. --JSM @@ -138,15 +145,15 @@ mkUnique :: Char -> Int -> Unique -- Builds a unique from pieces mkUnique c i = MkUnique (tag .|. bits) where - tag = ord c `shiftL` 24 - bits = i .&. 16777215 {-``0x00ffffff''-} + tag = ord c `shiftL` UNIQUE_BITS + bits = i .&. uniqueMask unpkUnique (MkUnique u) = let -- as long as the Char may have its eighth bit set, we -- really do need the logical right-shift here! - tag = chr (u `shiftR` 24) - i = u .&. 16777215 {-``0x00ffffff''-} + tag = chr (u `shiftR` UNIQUE_BITS) + i = u .&. uniqueMask in (tag, i) diff --git a/compiler/cbits/genSym.c b/compiler/cbits/genSym.c index 70ea417..725a310 100644 --- a/compiler/cbits/genSym.c +++ b/compiler/cbits/genSym.c @@ -1,18 +1,35 @@ - +#include #include "Rts.h" +#include "Unique.h" static HsInt GenSymCounter = 0; static HsInt GenSymInc = 1; +#define UNIQUE_MASK ((1ULL << UNIQUE_BITS) - 1) + +STATIC_INLINE void checkUniqueRange(HsInt u STG_UNUSED) { +#if DEBUG + // Uh oh! We will overflow next time a unique is requested. + assert(h != UNIQUE_MASK); +#endif +} + HsInt genSym(void) { #if defined(THREADED_RTS) if (n_capabilities == 1) { - return GenSymCounter = (GenSymCounter + GenSymInc) & 0xFFFFFF; + GenSymCounter = (GenSymCounter + GenSymInc) & UNIQUE_MASK; + checkUniqueRange(GenSymCounter); + return GenSymCounter; } else { - return atomic_inc((StgWord *)&GenSymCounter, GenSymInc) & 0xFFFFFF; + HsInt n = atomic_inc((StgWord *)&GenSymCounter, GenSymInc) + & UNIQUE_MASK; + checkUniqueRange(n); + return n; } #else - return GenSymCounter = (GenSymCounter + GenSymInc) & 0xFFFFFF; + GenSymCounter = (GenSymCounter + GenSymInc) & UNIQUE_MASK; + checkUniqueRange(GenSymCounter); + return GenSymCounter; #endif } From git at git.haskell.org Fri Dec 16 00:56:21 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Dec 2016 00:56:21 +0000 (UTC) Subject: [commit: ghc] master: base: Add more POSIX types (fixes #12795) (ffc2327) Message-ID: <20161216005621.B9C1A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ffc2327070dbb664bdb407a804121eacb2a7c734/ghc >--------------------------------------------------------------- commit ffc2327070dbb664bdb407a804121eacb2a7c734 Author: Daniel Gröber Date: Thu Dec 15 18:58:59 2016 -0500 base: Add more POSIX types (fixes #12795) Test Plan: validate Reviewers: hvr, austin, RyanGlScott, bgamari Reviewed By: RyanGlScott, bgamari Subscribers: RyanGlScott, thomie, erikd Differential Revision: https://phabricator.haskell.org/D2664 GHC Trac Issues: #12795 >--------------------------------------------------------------- ffc2327070dbb664bdb407a804121eacb2a7c734 libraries/base/System/Posix/Types.hs | 62 ++++++++++++++++++++++++++++++++++-- libraries/base/changelog.md | 3 ++ libraries/base/configure.ac | 8 +++++ libraries/base/include/CTypes.h | 10 ++++-- 4 files changed, 78 insertions(+), 5 deletions(-) diff --git a/libraries/base/System/Posix/Types.hs b/libraries/base/System/Posix/Types.hs index 67c38aa..0e9e2ae 100644 --- a/libraries/base/System/Posix/Types.hs +++ b/libraries/base/System/Posix/Types.hs @@ -71,6 +71,30 @@ module System.Posix.Types ( #if defined(HTYPE_RLIM_T) CRLim(..), #endif +#if defined(HTYPE_BLKSIZE_T) + CBlkSize(..), +#endif +#if defined(HTYPE_BLKCNT_T) + CBlkCnt(..), +#endif +#if defined(HTYPE_CLOCKID_T) + CClockId(..), +#endif +#if defined(HTYPE_FSBLKCNT_T) + CFsBlkCnt(..), +#endif +#if defined(HTYPE_FSFILCNT_T) + CFsFilCnt(..), +#endif +#if defined(HTYPE_ID_T) + CId(..), +#endif +#if defined(HTYPE_KEY_T) + CKey(..), +#endif +#if defined(HTYPE_TIMER_T) + CTimer(..), +#endif Fd(..), @@ -108,6 +132,9 @@ import GHC.Base import GHC.Enum import GHC.Num import GHC.Real +#if defined(HTYPE_TIMER_T) +import GHC.Float +#endif -- import GHC.Prim import GHC.Read import GHC.Show @@ -157,8 +184,38 @@ INTEGRAL_TYPE(CTcflag,HTYPE_TCFLAG_T) INTEGRAL_TYPE(CRLim,HTYPE_RLIM_T) #endif --- ToDo: blksize_t, clockid_t, blkcnt_t, fsblkcnt_t, fsfilcnt_t, id_t, key_t --- suseconds_t, timer_t, useconds_t +#if defined(HTYPE_BLKSIZE_T) +-- | @since 4.10.0.0 +INTEGRAL_TYPE_WITH_CTYPE(CBlkSize,blksize_t,HTYPE_BLKSIZE_T) +#endif +#if defined(HTYPE_BLKCNT_T) +-- | @since 4.10.0.0 +INTEGRAL_TYPE_WITH_CTYPE(CBlkCnt,blkcnt_t,HTYPE_BLKCNT_T) +#endif +#if defined(HTYPE_CLOCKID_T) +-- | @since 4.10.0.0 +INTEGRAL_TYPE_WITH_CTYPE(CClockId,clockid_t,HTYPE_CLOCKID_T) +#endif +#if defined(HTYPE_FSBLKCNT_T) +-- | @since 4.10.0.0 +INTEGRAL_TYPE_WITH_CTYPE(CFsBlkCnt,fsblkcnt_t,HTYPE_FSBLKCNT_T) +#endif +#if defined(HTYPE_FSFILCNT_T) +-- | @since 4.10.0.0 +INTEGRAL_TYPE_WITH_CTYPE(CFsFilCnt,fsfilcnt_t,HTYPE_FSFILCNT_T) +#endif +#if defined(HTYPE_ID_T) +-- | @since 4.10.0.0 +INTEGRAL_TYPE_WITH_CTYPE(CId,id_t,HTYPE_ID_T) +#endif +#if defined(HTYPE_KEY_T) +-- | @since 4.10.0.0 +INTEGRAL_TYPE_WITH_CTYPE(CKey,key_t,HTYPE_KEY_T) +#endif +#if defined(HTYPE_TIMER_T) +-- | @since 4.10.0.0 +FLOATING_TYPE_WITH_CTYPE(CTimer,timer_t,HTYPE_TIMER_T) +#endif -- Make an Fd type rather than using CInt everywhere INTEGRAL_TYPE(Fd,CInt) @@ -184,4 +241,3 @@ type ProcessID = CPid type FileOffset = COff type ProcessGroupID = CPid type Limit = CLong - diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 5039b64..d2e738b 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -30,6 +30,9 @@ * Added `Eq1`, `Ord1`, `Read1` and `Show1` instances for `NonEmpty`. + * Add wrappers for `blksize_t`, `blkcnt_t`, `clockid_t`, `fsblkcnt_t`, + `fsfilcnt_t`, `id_t`, `key_t` and `timer_t` to System.Posix.Types (#12795) + * Raw buffer operations in `GHC.IO.FD` are now strict in the buffer, offset, and length operations (#9696) ## 4.9.0.0 *May 2016* diff --git a/libraries/base/configure.ac b/libraries/base/configure.ac index 8098bc7..e6c8a9b 100644 --- a/libraries/base/configure.ac +++ b/libraries/base/configure.ac @@ -148,6 +148,14 @@ FPTOOLS_CHECK_HTYPE(tcflag_t) FPTOOLS_CHECK_HTYPE(nlink_t) FPTOOLS_CHECK_HTYPE(ssize_t) FPTOOLS_CHECK_HTYPE(rlim_t) +FPTOOLS_CHECK_HTYPE(blksize_t) +FPTOOLS_CHECK_HTYPE(blkcnt_t) +FPTOOLS_CHECK_HTYPE(clockid_t) +FPTOOLS_CHECK_HTYPE(fsblkcnt_t) +FPTOOLS_CHECK_HTYPE(fsfilcnt_t) +FPTOOLS_CHECK_HTYPE(id_t) +FPTOOLS_CHECK_HTYPE(key_t) +FPTOOLS_CHECK_HTYPE(timer_t) FPTOOLS_CHECK_HTYPE(intptr_t) FPTOOLS_CHECK_HTYPE(uintptr_t) diff --git a/libraries/base/include/CTypes.h b/libraries/base/include/CTypes.h index 9cee4f7..9fa1e4a 100644 --- a/libraries/base/include/CTypes.h +++ b/libraries/base/include/CTypes.h @@ -29,11 +29,17 @@ newtype T = T B deriving (ARITHMETIC_CLASSES, INTEGRAL_CLASSES) \ deriving newtype (Read, Show); #define INTEGRAL_TYPE_WITH_CTYPE(T,THE_CTYPE,B) \ -newtype {-# CTYPE "THE_CTYPE" #-} T = T B deriving (ARITHMETIC_CLASSES, INTEGRAL_CLASSES) \ - deriving newtype (Read, Show); +newtype {-# CTYPE "THE_CTYPE" #-} T = T B \ + deriving (ARITHMETIC_CLASSES, INTEGRAL_CLASSES) \ + deriving newtype (Read, Show); #define FLOATING_TYPE(T,B) \ newtype T = T B deriving (ARITHMETIC_CLASSES, FLOATING_CLASSES) \ deriving newtype (Read, Show); +#define FLOATING_TYPE_WITH_CTYPE(T,THE_CTYPE,B) \ +newtype {-# CTYPE "THE_CTYPE" #-} T = T B \ + deriving (ARITHMETIC_CLASSES, FLOATING_CLASSES) \ + deriving newtype (Read, Show); + #endif From git at git.haskell.org Fri Dec 16 00:56:24 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Dec 2016 00:56:24 +0000 (UTC) Subject: [commit: ghc] master: Verify that known-key uniques fit in interface file (6fecb2a) Message-ID: <20161216005624.735453A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6fecb2a4dec6d1a4bfb5655ef5fc2a3e475954a4/ghc >--------------------------------------------------------------- commit 6fecb2a4dec6d1a4bfb5655ef5fc2a3e475954a4 Author: Ben Gamari Date: Thu Dec 15 19:00:00 2016 -0500 Verify that known-key uniques fit in interface file Here we introduce a debug check asserting that all uniques in knownKeyNames will fit in the space allowed in the interface file's symbol encoding. Test Plan: Validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2845 >--------------------------------------------------------------- 6fecb2a4dec6d1a4bfb5655ef5fc2a3e475954a4 compiler/basicTypes/Unique.hs | 10 ++++++++++ compiler/iface/BinIface.hs | 4 +++- compiler/prelude/PrelInfo.hs | 5 +++++ 3 files changed, 18 insertions(+), 1 deletion(-) diff --git a/compiler/basicTypes/Unique.hs b/compiler/basicTypes/Unique.hs index a6ac670..f93a4b1 100644 --- a/compiler/basicTypes/Unique.hs +++ b/compiler/basicTypes/Unique.hs @@ -36,6 +36,7 @@ module Unique ( newTagUnique, -- Used in CgCase initTyVarUnique, nonDetCmpUnique, + isValidKnownKeyUnique, -- Used in PrelInfo.knownKeyNamesOkay -- ** Making built-in uniques @@ -157,6 +158,15 @@ unpkUnique (MkUnique u) in (tag, i) +-- | The interface file symbol-table encoding assumes that known-key uniques fit +-- in 30-bits; verify this. +-- +-- See Note [Symbol table representation of names] in BinIface for details. +isValidKnownKeyUnique :: Unique -> Bool +isValidKnownKeyUnique u = + case unpkUnique u of + (c, x) -> ord c < 0xff && x <= (1 `shiftL` 22) + {- ************************************************************************ * * diff --git a/compiler/iface/BinIface.hs b/compiler/iface/BinIface.hs index 3de647d..ad1e845 100644 --- a/compiler/iface/BinIface.hs +++ b/compiler/iface/BinIface.hs @@ -293,7 +293,9 @@ serialiseName bh name _ = do -- 00xxxxxx xxxxxxxx xxxxxxxx xxxxxxxx -- A normal name. x is an index into the symbol table -- 10xxxxxx xxyyyyyy yyyyyyyy yyyyyyyy --- A known-key name. x is the Unique's Char, y is the int part +-- A known-key name. x is the Unique's Char, y is the int part. We assume that +-- all known-key uniques fit in this space. This is asserted by +-- PrelInfo.knownKeyNamesOkay. -- -- During serialization we check for known-key things using isKnownKeyName. -- During deserialization we use lookupKnownKeyName to get from the unique back diff --git a/compiler/prelude/PrelInfo.hs b/compiler/prelude/PrelInfo.hs index b9eb9da..471b61e 100644 --- a/compiler/prelude/PrelInfo.hs +++ b/compiler/prelude/PrelInfo.hs @@ -46,6 +46,7 @@ module PrelInfo ( #include "HsVersions.h" import KnownUniques +import Unique ( isValidKnownKeyUnique ) import ConLike ( ConLike(..) ) import THNames ( templateHaskellNames ) @@ -158,6 +159,10 @@ knownKeyNames -- | Check the known-key names list of consistency. knownKeyNamesOkay :: [Name] -> Maybe String knownKeyNamesOkay all_names + | ns@(_:_) <- filter (not . isValidKnownKeyUnique . getUnique) all_names + = Just $ " Out-of-range known-key uniques: [" + ++ intercalate ", " (map (occNameString . nameOccName) ns) ++ + "]" | null badNamesPairs = Nothing | otherwise From git at git.haskell.org Fri Dec 16 13:01:45 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Dec 2016 13:01:45 +0000 (UTC) Subject: [commit: ghc] master: Typos in comments (ed4cf03) Message-ID: <20161216130145.721A93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ed4cf039092a8cc5bea78dedb845f8e2db3f49b8/ghc >--------------------------------------------------------------- commit ed4cf039092a8cc5bea78dedb845f8e2db3f49b8 Author: Gabor Greif Date: Fri Dec 16 14:00:15 2016 +0100 Typos in comments >--------------------------------------------------------------- ed4cf039092a8cc5bea78dedb845f8e2db3f49b8 compiler/coreSyn/CoreUtils.hs | 2 +- compiler/llvmGen/LlvmCodeGen/Regs.hs | 2 +- compiler/main/GhcMake.hs | 2 +- compiler/simplCore/CallArity.hs | 2 +- compiler/simplCore/SetLevels.hs | 2 +- compiler/specialise/Rules.hs | 2 +- compiler/typecheck/TcGenFunctor.hs | 2 +- compiler/utils/BooleanFormula.hs | 2 +- compiler/vectorise/Vectorise/Vect.hs | 2 +- 9 files changed, 9 insertions(+), 9 deletions(-) diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index ef1555f..c611e0b 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -357,7 +357,7 @@ stripTicksTop p = go [] go ts other = (reverse ts, other) -- | Strip ticks satisfying a predicate from top of an expression, --- returning the remaining expresion +-- returning the remaining expression stripTicksTopE :: (Tickish Id -> Bool) -> Expr b -> Expr b stripTicksTopE p = go where go (Tick t e) | p t = go e diff --git a/compiler/llvmGen/LlvmCodeGen/Regs.hs b/compiler/llvmGen/LlvmCodeGen/Regs.hs index 1ee9fc1..186eda3 100644 --- a/compiler/llvmGen/LlvmCodeGen/Regs.hs +++ b/compiler/llvmGen/LlvmCodeGen/Regs.hs @@ -102,7 +102,7 @@ stgTBAA , (heapN, fsLit "heap", Just topN) , (rxN, fsLit "rx", Just heapN) , (baseN, fsLit "base", Just topN) - -- FIX: Not 100% sure if this heirarchy is complete. I think the big thing + -- FIX: Not 100% sure if this hierarchy is complete. I think the big thing -- is Sp is never aliased, so might want to change the hierarchy to have Sp -- on its own branch that is never aliased (e.g never use top as a TBAA -- node). diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs index aa50c3a..6b103c9 100644 --- a/compiler/main/GhcMake.hs +++ b/compiler/main/GhcMake.hs @@ -479,7 +479,7 @@ guessOutputFile = modifySession $ \env -> name_exe = do #if defined(mingw32_HOST_OS) - -- we must add the .exe extention unconditionally here, otherwise + -- we must add the .exe extension unconditionally here, otherwise -- when name has an extension of its own, the .exe extension will -- not be added by DriverPipeline.exeFileName. See #2248 name' <- fmap (<.> "exe") name diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs index 0186c67..a93fe1f 100644 --- a/compiler/simplCore/CallArity.hs +++ b/compiler/simplCore/CallArity.hs @@ -468,7 +468,7 @@ callArityAnal arity int (Lam v e) where (ae, e') = callArityAnal (arity - 1) (int `delVarSet` v) e --- Application. Increase arity for the called expresion, nothing to know about +-- Application. Increase arity for the called expression, nothing to know about -- the second callArityAnal arity int (App e (Type t)) = second (\e -> App e (Type t)) $ callArityAnal arity int e diff --git a/compiler/simplCore/SetLevels.hs b/compiler/simplCore/SetLevels.hs index dc36a6c..ef98e7b 100644 --- a/compiler/simplCore/SetLevels.hs +++ b/compiler/simplCore/SetLevels.hs @@ -1033,7 +1033,7 @@ lookupVar le v = case lookupVarEnv (le_env le) v of _ -> Var v abstractVars :: Level -> LevelEnv -> DVarSet -> [OutVar] - -- Find the variables in fvs, free vars of the target expresion, + -- Find the variables in fvs, free vars of the target expression, -- whose level is greater than the destination level -- These are the ones we are going to abstract out -- diff --git a/compiler/specialise/Rules.hs b/compiler/specialise/Rules.hs index 7909bdc..42cb13e 100644 --- a/compiler/specialise/Rules.hs +++ b/compiler/specialise/Rules.hs @@ -703,7 +703,7 @@ match _ _ e at Tick{} _ -- Consider matching -- \x->f against \f->f -- When we meet the lambdas we must remember to rename f to f' in the --- second expresion. The RnEnv2 does that. +-- second expression. The RnEnv2 does that. -- -- Consider matching -- forall a. \b->b against \a->3 diff --git a/compiler/typecheck/TcGenFunctor.hs b/compiler/typecheck/TcGenFunctor.hs index 1f0df61..5679f9f 100644 --- a/compiler/typecheck/TcGenFunctor.hs +++ b/compiler/typecheck/TcGenFunctor.hs @@ -727,7 +727,7 @@ Deriving Functor, Foldable, and Traversable all require generating expressions which perform an operation on each argument of a data constructor depending on the argument's type. In particular, a generated operation can be different depending on whether the type mentions the last type variable of the datatype -(e.g., if you have data T a = MkT a Int, then a generated foldr expresion would +(e.g., if you have data T a = MkT a Int, then a generated foldr expression would fold over the first argument of MkT, but not the second). This pattern is abstracted with the FFoldType datatype, which provides hooks diff --git a/compiler/utils/BooleanFormula.hs b/compiler/utils/BooleanFormula.hs index 13f6e21..1509321 100644 --- a/compiler/utils/BooleanFormula.hs +++ b/compiler/utils/BooleanFormula.hs @@ -86,7 +86,7 @@ The smart constructors (`mkAnd` and `mkOr`) do some attempt to simplify expressi Implemented by mkAnd' / mkOr' 3. Conjunction with false, disjunction with true is simplified, i.e. `mkAnd [mkFalse,x]` becomes `mkFalse`. - 4. Common subexpresion elimination: + 4. Common subexpression elimination: `mkAnd [x,x,y]` is reduced to just `mkAnd [x,y]`. This simplification is not exhaustive, in the sense that it will not produce diff --git a/compiler/vectorise/Vectorise/Vect.hs b/compiler/vectorise/Vectorise/Vect.hs index fac1ab4..436c78e 100644 --- a/compiler/vectorise/Vectorise/Vect.hs +++ b/compiler/vectorise/Vectorise/Vect.hs @@ -84,7 +84,7 @@ vRec vs es = (Rec (zip vvs ves), Rec (zip lvs les)) (vvs, lvs) = unzip vs (ves, les) = unzip es --- |Make a vectorised let expresion. +-- |Make a vectorised let expression. -- vLet :: VBind -> VExpr -> VExpr vLet = zipWithVect Let From git at git.haskell.org Fri Dec 16 17:11:32 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Dec 2016 17:11:32 +0000 (UTC) Subject: [commit: ghc] master: DynFlags: Rip out remnants of WarnContextQuantification (13c1fc4) Message-ID: <20161216171132.C14203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/13c1fc4dfc925afa328a6be9db191b11bf96d4a0/ghc >--------------------------------------------------------------- commit 13c1fc4dfc925afa328a6be9db191b11bf96d4a0 Author: Ben Gamari Date: Fri Dec 16 11:58:55 2016 -0500 DynFlags: Rip out remnants of WarnContextQuantification Test Plan: Validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2862 GHC Trac Issues: #11221 >--------------------------------------------------------------- 13c1fc4dfc925afa328a6be9db191b11bf96d4a0 compiler/main/DynFlags.hs | 3 --- docs/users_guide/glasgow_exts.rst | 6 ++---- 2 files changed, 2 insertions(+), 7 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index db234bd..f1bb6c0 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -614,7 +614,6 @@ data WarningFlag = | Opt_WarnUnusedMatches | Opt_WarnUnusedTypePatterns | Opt_WarnUnusedForalls - | Opt_WarnContextQuantification -- remove in 8.2 | Opt_WarnWarningsDeprecations | Opt_WarnDeprecatedFlags | Opt_WarnAMP -- Introduced in GHC 7.8, obsolete since 7.10 @@ -3466,8 +3465,6 @@ wWarningFlagsDeps = [ flagSpec "dodgy-foreign-imports" Opt_WarnDodgyForeignImports, flagSpec "dodgy-imports" Opt_WarnDodgyImports, flagSpec "empty-enumerations" Opt_WarnEmptyEnumerations, - depFlagSpec "context-quantification" Opt_WarnContextQuantification - "it is subsumed by an error message that cannot be disabled", depFlagSpec "duplicate-constraints" Opt_WarnDuplicateConstraints "it is subsumed by -Wredundant-constraints", flagSpec "redundant-constraints" Opt_WarnRedundantConstraints, diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 5db8bdc..b28edf7 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -9343,10 +9343,8 @@ example: :: newtype Swizzle' = MkSwizzle' (Ord a => [a] -> [a]) -As of GHC 7.10, this is deprecated. The -:ghc-flag:`-Wcontext-quantification` flag detects this situation and issues -a warning. In GHC 8.0 this flag was deprecated and declarations such as -``MkSwizzle'`` will cause an out-of-scope error. +Since GHC 8.0 declarations such as ``MkSwizzle'`` will cause an out-of-scope +error. As for type signatures, implicit quantification happens for non-overloaded types too. So if you write this: :: From git at git.haskell.org Fri Dec 16 17:11:35 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Dec 2016 17:11:35 +0000 (UTC) Subject: [commit: ghc] master: Packages: Kill unused UnitId argument to isDllName (c889df8) Message-ID: <20161216171135.894BD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c889df86d7bc9eb4cd53e38c81feecaf5f932678/ghc >--------------------------------------------------------------- commit c889df86d7bc9eb4cd53e38c81feecaf5f932678 Author: Ben Gamari Date: Fri Dec 16 11:59:26 2016 -0500 Packages: Kill unused UnitId argument to isDllName Test Plan: Validate Reviewers: austin, simonmar Subscribers: thomie, ezyang Differential Revision: https://phabricator.haskell.org/D2866 >--------------------------------------------------------------- c889df86d7bc9eb4cd53e38c81feecaf5f932678 compiler/cmm/CLabel.hs | 2 +- compiler/main/Packages.hs | 4 ++-- compiler/main/TidyPgm.hs | 23 +++++++++++------------ compiler/stgSyn/StgSyn.hs | 6 ++---- 4 files changed, 16 insertions(+), 19 deletions(-) diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs index 3fd081c..811d8e9 100644 --- a/compiler/cmm/CLabel.hs +++ b/compiler/cmm/CLabel.hs @@ -952,7 +952,7 @@ labelDynamic dflags this_pkg this_mod lbl = -- is the RTS in a DLL or not? RtsLabel _ -> (WayDyn `elem` ways dflags) && (this_pkg /= rtsUnitId) - IdLabel n _ _ -> isDllName dflags this_pkg this_mod n + IdLabel n _ _ -> isDllName dflags this_mod n -- When compiling in the "dyn" way, each package is to be linked into -- its own shared library. diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index 86a3735..b6b5e3c 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -1747,11 +1747,11 @@ displayInstalledUnitId dflags uid = fmap sourcePackageIdString (lookupInstalledPackage dflags uid) -- | Will the 'Name' come from a dynamically linked library? -isDllName :: DynFlags -> UnitId {- not used -} -> Module -> Name -> Bool +isDllName :: DynFlags -> Module -> Name -> Bool -- Despite the "dll", I think this function just means that -- the symbol comes from another dynamically-linked package, -- and applies on all platforms, not just Windows -isDllName dflags _this_pkg this_mod name +isDllName dflags this_mod name | WayDyn `notElem` ways dflags = False | Just mod <- nameModule_maybe name -- Issue #8696 - when GHC is dynamically linked, it will attempt diff --git a/compiler/main/TidyPgm.hs b/compiler/main/TidyPgm.hs index 9f2723c..c4057fc 100644 --- a/compiler/main/TidyPgm.hs +++ b/compiler/main/TidyPgm.hs @@ -1132,18 +1132,15 @@ tidyTopBinds hsc_env this_mod unfold_env init_occ_env binds init_env = (init_occ_env, emptyVarEnv) - this_pkg = thisPackage dflags - tidy _ env [] = (env, []) tidy cvt_integer env (b:bs) - = let (env1, b') = tidyTopBind dflags this_pkg this_mod + = let (env1, b') = tidyTopBind dflags this_mod cvt_integer unfold_env env b (env2, bs') = tidy cvt_integer env1 bs in (env2, b':bs') ------------------------ tidyTopBind :: DynFlags - -> UnitId -> Module -> (Integer -> CoreExpr) -> UnfoldEnv @@ -1151,17 +1148,19 @@ tidyTopBind :: DynFlags -> CoreBind -> (TidyEnv, CoreBind) -tidyTopBind dflags this_pkg this_mod cvt_integer unfold_env +tidyTopBind dflags this_mod cvt_integer unfold_env (occ_env,subst1) (NonRec bndr rhs) = (tidy_env2, NonRec bndr' rhs') where Just (name',show_unfold) = lookupVarEnv unfold_env bndr - caf_info = hasCafRefs dflags this_pkg this_mod (subst1, cvt_integer) (idArity bndr) rhs - (bndr', rhs') = tidyTopPair dflags show_unfold tidy_env2 caf_info name' (bndr, rhs) + caf_info = hasCafRefs dflags this_mod (subst1, cvt_integer) + (idArity bndr) rhs + (bndr', rhs') = tidyTopPair dflags show_unfold tidy_env2 caf_info name' + (bndr, rhs) subst2 = extendVarEnv subst1 bndr bndr' tidy_env2 = (occ_env, subst2) -tidyTopBind dflags this_pkg this_mod cvt_integer unfold_env +tidyTopBind dflags this_mod cvt_integer unfold_env (occ_env, subst1) (Rec prs) = (tidy_env2, Rec prs') where @@ -1179,7 +1178,7 @@ tidyTopBind dflags this_pkg this_mod cvt_integer unfold_env -- the CafInfo for a recursive group says whether *any* rhs in -- the group may refer indirectly to a CAF (because then, they all do). caf_info - | or [ mayHaveCafRefs (hasCafRefs dflags this_pkg this_mod + | or [ mayHaveCafRefs (hasCafRefs dflags this_mod (subst1, cvt_integer) (idArity bndr) rhs) | (bndr,rhs) <- prs ] = MayHaveCafRefs @@ -1331,15 +1330,15 @@ type CafRefEnv = (VarEnv Id, Integer -> CoreExpr) -- The Integer -> CoreExpr is the desugaring function for Integer literals -- See Note [Disgusting computation of CafRefs] -hasCafRefs :: DynFlags -> UnitId -> Module +hasCafRefs :: DynFlags -> Module -> CafRefEnv -> Arity -> CoreExpr -> CafInfo -hasCafRefs dflags this_pkg this_mod p@(_,cvt_integer) arity expr +hasCafRefs dflags this_mod p@(_,cvt_integer) arity expr | is_caf || mentions_cafs = MayHaveCafRefs | otherwise = NoCafRefs where mentions_cafs = cafRefsE p expr - is_dynamic_name = isDllName dflags this_pkg this_mod + is_dynamic_name = isDllName dflags this_mod is_caf = not (arity > 0 || rhsIsStatic (targetPlatform dflags) is_dynamic_name cvt_integer expr) -- NB. we pass in the arity of the expression, which is expected diff --git a/compiler/stgSyn/StgSyn.hs b/compiler/stgSyn/StgSyn.hs index b553cd7..3ec37ee 100644 --- a/compiler/stgSyn/StgSyn.hs +++ b/compiler/stgSyn/StgSyn.hs @@ -98,18 +98,16 @@ data GenStgArg occ isDllConApp :: DynFlags -> Module -> DataCon -> [StgArg] -> Bool isDllConApp dflags this_mod con args | platformOS (targetPlatform dflags) == OSMinGW32 - = isDllName dflags this_pkg this_mod (dataConName con) || any is_dll_arg args + = isDllName dflags this_mod (dataConName con) || any is_dll_arg args | otherwise = False where -- NB: typePrimRep is legit because any free variables won't have -- unlifted type (there are no unlifted things at top level) is_dll_arg :: StgArg -> Bool is_dll_arg (StgVarArg v) = isAddrRep (typePrimRep (idType v)) - && isDllName dflags this_pkg this_mod (idName v) + && isDllName dflags this_mod (idName v) is_dll_arg _ = False - this_pkg = thisPackage dflags - -- True of machine addresses; these are the things that don't -- work across DLLs. The key point here is that VoidRep comes -- out False, so that a top level nullary GADT constructor is From git at git.haskell.org Fri Dec 16 17:11:38 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Dec 2016 17:11:38 +0000 (UTC) Subject: [commit: ghc] master: CLabel: Kill redundant UnitId argument from labelDynamic (5bf344b) Message-ID: <20161216171138.603983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5bf344b7f4e1538fbc019896ae07ae3ec2a18207/ghc >--------------------------------------------------------------- commit 5bf344b7f4e1538fbc019896ae07ae3ec2a18207 Author: Ben Gamari Date: Fri Dec 16 11:59:49 2016 -0500 CLabel: Kill redundant UnitId argument from labelDynamic It already has access to the current package's UnitId via the Module. Edward Yang pointed out that there is one wrinkle, however: the following invariant isn't true at all stages of compilation, if I am compiling the module (this_mod :: Module), then thisPackage dflags == moduleUnitId this_mod. Specifically, this is only true after desugaring; it may be broken when typechecking an indefinite signature. However, it's safe to assume this in the native codegen. I've updated Note to state this invariant more directly. Test Plan: Validate Reviewers: austin, ezyang, simonmar Reviewed By: ezyang, simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2863 >--------------------------------------------------------------- 5bf344b7f4e1538fbc019896ae07ae3ec2a18207 compiler/cmm/CLabel.hs | 8 +++++--- compiler/deSugar/Desugar.hs | 2 ++ compiler/nativeGen/PIC.hs | 16 ++++++++-------- compiler/typecheck/TcRnTypes.hs | 7 +++++++ 4 files changed, 22 insertions(+), 11 deletions(-) diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs index 811d8e9..0f3410a 100644 --- a/compiler/cmm/CLabel.hs +++ b/compiler/cmm/CLabel.hs @@ -946,8 +946,8 @@ idInfoLabelType info = -- @labelDynamic@ returns @True@ if the label is located -- in a DLL, be it a data reference or not. -labelDynamic :: DynFlags -> UnitId -> Module -> CLabel -> Bool -labelDynamic dflags this_pkg this_mod lbl = +labelDynamic :: DynFlags -> Module -> CLabel -> Bool +labelDynamic dflags this_mod lbl = case lbl of -- is the RTS in a DLL or not? RtsLabel _ -> (WayDyn `elem` ways dflags) && (this_pkg /= rtsUnitId) @@ -989,7 +989,9 @@ labelDynamic dflags this_pkg this_mod lbl = -- Note that DynamicLinkerLabels do NOT require dynamic linking themselves. _ -> False - where os = platformOS (targetPlatform dflags) + where + os = platformOS (targetPlatform dflags) + this_pkg = moduleUnitId this_mod ----------------------------------------------------------------------------- diff --git a/compiler/deSugar/Desugar.hs b/compiler/deSugar/Desugar.hs index 28ec706..e73f12f 100644 --- a/compiler/deSugar/Desugar.hs +++ b/compiler/deSugar/Desugar.hs @@ -369,6 +369,8 @@ deSugar hsc_env ; usages <- mkUsageInfo hsc_env mod (imp_mods imports) used_names dep_files merged -- id_mod /= mod when we are processing an hsig, but hsigs -- never desugared and compiled (there's no code!) + -- Consequently, this should hold for any ModGuts that make + -- past desugaring. See Note [Identity versus semantic module]. ; MASSERT( id_mod == mod ) ; let mod_guts = ModGuts { diff --git a/compiler/nativeGen/PIC.hs b/compiler/nativeGen/PIC.hs index 2529f91..babceac 100644 --- a/compiler/nativeGen/PIC.hs +++ b/compiler/nativeGen/PIC.hs @@ -241,7 +241,7 @@ howToAccessLabel dflags _ OSMinGW32 this_mod _ lbl -- If the target symbol is in another PE we need to access it via the -- appropriate __imp_SYMBOL pointer. - | labelDynamic dflags (thisPackage dflags) this_mod lbl + | labelDynamic dflags this_mod lbl = AccessViaSymbolPtr -- Target symbol is in the same PE as the caller, so just access it directly. @@ -259,7 +259,7 @@ howToAccessLabel dflags _ OSMinGW32 this_mod _ lbl -- howToAccessLabel dflags arch OSDarwin this_mod DataReference lbl -- data access to a dynamic library goes via a symbol pointer - | labelDynamic dflags (thisPackage dflags) this_mod lbl + | labelDynamic dflags this_mod lbl = AccessViaSymbolPtr -- when generating PIC code, all cross-module data references must @@ -283,7 +283,7 @@ howToAccessLabel dflags arch OSDarwin this_mod JumpReference lbl -- stack alignment is only right for regular calls. -- Therefore, we have to go via a symbol pointer: | arch == ArchX86 || arch == ArchX86_64 - , labelDynamic dflags (thisPackage dflags) this_mod lbl + , labelDynamic dflags this_mod lbl = AccessViaSymbolPtr @@ -292,7 +292,7 @@ howToAccessLabel dflags arch OSDarwin this_mod _ lbl -- not needed on x86_64 because Apple's new linker, ld64, generates -- them automatically. | arch /= ArchX86_64 - , labelDynamic dflags (thisPackage dflags) this_mod lbl + , labelDynamic dflags this_mod lbl = AccessViaStub | otherwise @@ -344,7 +344,7 @@ howToAccessLabel dflags arch os this_mod DataReference lbl | osElfTarget os = case () of -- A dynamic label needs to be accessed via a symbol pointer. - _ | labelDynamic dflags (thisPackage dflags) this_mod lbl + _ | labelDynamic dflags this_mod lbl -> AccessViaSymbolPtr -- For PowerPC32 -fPIC, we have to access even static data @@ -372,17 +372,17 @@ howToAccessLabel dflags arch os this_mod DataReference lbl howToAccessLabel dflags arch os this_mod CallReference lbl | osElfTarget os - , labelDynamic dflags (thisPackage dflags) this_mod lbl && not (gopt Opt_PIC dflags) + , labelDynamic dflags this_mod lbl && not (gopt Opt_PIC dflags) = AccessDirectly | osElfTarget os , arch /= ArchX86 - , labelDynamic dflags (thisPackage dflags) this_mod lbl && gopt Opt_PIC dflags + , labelDynamic dflags this_mod lbl && gopt Opt_PIC dflags = AccessViaStub howToAccessLabel dflags _ os this_mod _ lbl | osElfTarget os - = if labelDynamic dflags (thisPackage dflags) this_mod lbl + = if labelDynamic dflags this_mod lbl then AccessViaSymbolPtr else AccessDirectly diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index 4833839..a79b1a0 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -439,6 +439,13 @@ data FrontendResult -- signatures (we just generate blank object files for -- hsig files.) -- +-- A corrolary of this is that the following invariant holds at any point +-- past desugaring, +-- +-- if I have a Module, this_mod, in hand representing the module +-- currently being compiled, +-- then moduleUnitId this_mod == thisPackage dflags +-- -- - For any code involving Names, we want semantic modules. -- See lookupIfaceTop in IfaceEnv, mkIface and addFingerprints -- in MkIface, and tcLookupGlobal in TcEnv From git at git.haskell.org Fri Dec 16 17:11:41 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Dec 2016 17:11:41 +0000 (UTC) Subject: [commit: ghc] master: Make up a module name for c-- files (222e99d) Message-ID: <20161216171141.2BCE23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/222e99d9e6b24c17a67c07d24d05999701b83e96/ghc >--------------------------------------------------------------- commit 222e99d9e6b24c17a67c07d24d05999701b83e96 Author: Ben Gamari Date: Fri Dec 16 12:00:27 2016 -0500 Make up a module name for c-- files Summary: We used to pass a bottoming Module to the NCG, which resulted in panics when `-v` was used due to debug output (see #11784). Instead we make up a module name. This is a bit scary since `PIC.howToAccessLabel` might actually use the Module, but if it wasn't crashing before I suppose it's fine. Test Plan: `touch hi.cmm; ghc -v2 -c -dcmm-lint hi.cmm` Reviewers: austin, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2864 GHC Trac Issues: #11784 >--------------------------------------------------------------- 222e99d9e6b24c17a67c07d24d05999701b83e96 compiler/main/HscMain.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index 141f59f..9a64794 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -1363,10 +1363,13 @@ hscCompileCmmFile hsc_env filename output_filename = runHsc hsc_env $ do dumpIfSet_dyn dflags Opt_D_dump_cmm_verbose "Parsed Cmm" (ppr cmm) (_, cmmgroup) <- cmmPipeline hsc_env initTopSRT cmm rawCmms <- cmmToRawCmm dflags (Stream.yield cmmgroup) - _ <- codeOutput dflags no_mod output_filename no_loc NoStubs [] rawCmms + let -- Make up a module name to give the NCG. We can't pass bottom here + -- lest we reproduce #11784. + mod_name = mkModuleName $ "Cmm$" ++ FilePath.takeFileName filename + cmm_mod = mkModule (thisPackage dflags) mod_name + _ <- codeOutput dflags cmm_mod output_filename no_loc NoStubs [] rawCmms return () where - no_mod = panic "hscCompileCmmFile: no_mod" no_loc = ModLocation{ ml_hs_file = Just filename, ml_hi_file = panic "hscCompileCmmFile: no hi file", ml_obj_file = panic "hscCompileCmmFile: no obj file" } From git at git.haskell.org Sat Dec 17 01:58:10 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Dec 2016 01:58:10 +0000 (UTC) Subject: [commit: ghc] master: Fix string merging with -split-sections (4026b45) Message-ID: <20161217015810.7FAB43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4026b452817e9d4241691c58d131904bd0eb1fec/ghc >--------------------------------------------------------------- commit 4026b452817e9d4241691c58d131904bd0eb1fec Author: Simon Brenner Date: Fri Dec 16 12:14:36 2016 -0500 Fix string merging with -split-sections The added flags for string literal merging ended up printed in the middle of the section name when -split-sections was enabled. Break it up to put the flags after the name. Test Plan: validate with SplitSections=YES Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2865 GHC Trac Issues: #9577 >--------------------------------------------------------------- 4026b452817e9d4241691c58d131904bd0eb1fec compiler/nativeGen/PprBase.hs | 17 ++++++++++++++--- 1 file changed, 14 insertions(+), 3 deletions(-) diff --git a/compiler/nativeGen/PprBase.hs b/compiler/nativeGen/PprBase.hs index 10ed2fb..e05b2b5 100644 --- a/compiler/nativeGen/PprBase.hs +++ b/compiler/nativeGen/PprBase.hs @@ -85,6 +85,10 @@ doubleToBytes d -- If -split-section was specified, include the suffix label, otherwise just -- print the section type. For Darwin, where subsections-for-symbols are -- used instead, only print section type. +-- +-- For string literals, additional flags are specified to enable merging of +-- identical strings in the linker. With -split-sections each string also gets +-- a unique section to allow strings from unused code to be GC'd. pprSectionHeader :: Platform -> Section -> SDoc pprSectionHeader platform (Section t suffix) = @@ -98,7 +102,8 @@ pprGNUSectionHeader t suffix = sdocWithDynFlags $ \dflags -> let splitSections = gopt Opt_SplitSections dflags subsection | splitSections = char '.' <> ppr suffix | otherwise = empty - in text ".section " <> ptext (header dflags) <> subsection + in text ".section " <> ptext (header dflags) <> subsection <> + flags dflags where header dflags = case t of Text -> sLit ".text" @@ -109,10 +114,16 @@ pprGNUSectionHeader t suffix = sdocWithDynFlags $ \dflags -> ReadOnlyData16 -> sLit ".rodata.cst16" CString | OSMinGW32 <- platformOS (targetPlatform dflags) - -> sLit ".rdata,\"dr\"" - | otherwise -> sLit ".rodata.str1.1,\"aMS\", at progbits,1" + -> sLit ".rdata" + | otherwise -> sLit ".rodata.str" OtherSection _ -> panic "PprBase.pprGNUSectionHeader: unknown section type" + flags dflags = case t of + CString + | OSMinGW32 <- platformOS (targetPlatform dflags) + -> text ",\"dr\"" + | otherwise -> text ",\"aMS\", at progbits,1" + _ -> empty -- XCOFF doesn't support relocating label-differences, so we place all -- RO sections into .text[PR] sections From git at git.haskell.org Sat Dec 17 01:58:13 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Dec 2016 01:58:13 +0000 (UTC) Subject: [commit: ghc] master: Enable split sections by default where possible (8f71d95) Message-ID: <20161217015813.41A133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8f71d9581ee0a1826c0105e51a7048f0c7669492/ghc >--------------------------------------------------------------- commit 8f71d9581ee0a1826c0105e51a7048f0c7669492 Author: Simon Brenner Date: Fri Dec 16 12:16:05 2016 -0500 Enable split sections by default where possible On non-windows platforms with GNU ld, enable SplitSections in the GHC build by default. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: DemiMarie, thomie Differential Revision: https://phabricator.haskell.org/D1800 GHC Trac Issues: #11445 >--------------------------------------------------------------- 8f71d9581ee0a1826c0105e51a7048f0c7669492 mk/config.mk.in | 21 ++++++++++++++++----- 1 file changed, 16 insertions(+), 5 deletions(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index 06c12bf..5141ccf 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -339,8 +339,12 @@ SupportsSplitObjs := $(strip \ $(filter NO,$(GhcUnregisterised))),\ YES,NO)) -# By default, enable SplitObjs for the libraries if this build supports it -SplitObjs=$(SupportsSplitObjs) +# By default, enable SplitObjs for the libraries if this build supports it. +# Unless SplitSections is enabled - then let that take precedence. +SplitObjs = $(strip \ + $(if $(and $(filter YES,$(SupportsSplitObjs)),\ + $(filter NO,$(SplitSections))),\ + YES,NO)) # ---------------------------------------------------------------------------- # Section splitting @@ -349,9 +353,16 @@ SplitObjs=$(SupportsSplitObjs) # like SplitObjs, but doesn't require post-processing and splitting of object # files. # -# Set SplitSections=YES in your build.mk to enable. - -SplitSections=NO +# Set SplitSections=YES or NO in your build.mk to override the default. +# +# This is not supported on Darwin (where you can use subsections-via-symbols +# instead) and Windows is not yet working. (See #11445 and related tickets.) +OsSupportsSplitSections=$(strip $(if $(filter $(TargetOS_CPP),mingw32 darwin),NO,YES)) +SupportsSplitSections = $(strip \ + $(if $(and $(filter YES,$(OsSupportsSplitSections)),\ + $(filter YES,$(LdIsGNULd))),\ + YES,NO)) +SplitSections ?= $(SupportsSplitSections) # ---------------------------------------------------------------------------- From git at git.haskell.org Sat Dec 17 01:58:16 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Dec 2016 01:58:16 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add test for #12993 (c8ed1bd) Message-ID: <20161217015816.750173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c8ed1bdc02e68f8cab32a6a44520b896d37310a5/ghc >--------------------------------------------------------------- commit c8ed1bdc02e68f8cab32a6a44520b896d37310a5 Author: Ben Gamari Date: Fri Dec 16 16:47:45 2016 -0500 testsuite: Add test for #12993 >--------------------------------------------------------------- c8ed1bdc02e68f8cab32a6a44520b896d37310a5 testsuite/tests/th/T12993.hs | 4 ++++ testsuite/tests/th/T12993_Lib.hs | 4 ++++ testsuite/tests/th/all.T | 2 ++ 3 files changed, 10 insertions(+) diff --git a/testsuite/tests/th/T12993.hs b/testsuite/tests/th/T12993.hs new file mode 100644 index 0000000..6082669 --- /dev/null +++ b/testsuite/tests/th/T12993.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE TemplateHaskell #-} +module T12993 where +import T12993_Lib +f = $(q) diff --git a/testsuite/tests/th/T12993_Lib.hs b/testsuite/tests/th/T12993_Lib.hs new file mode 100644 index 0000000..441b783 --- /dev/null +++ b/testsuite/tests/th/T12993_Lib.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE TemplateHaskell #-} +module T12993_Lib (q) where +data X = X { x :: Int } +q = [|x|] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index c2c9fa2..bb11528 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -445,3 +445,5 @@ test('T12788', extra_clean(['T12788_Lib.hi', 'T12788_Lib.o']), multimod_compile_fail, ['T12788.hs', '-v0 ' + config.ghc_th_way_flags]) test('T12977', normal, compile, ['-v0']) +test('T12993', expect_broken(12993), multimod_compile, + ['T12993.hs', '-v0']) \ No newline at end of file From git at git.haskell.org Sat Dec 17 02:19:08 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Dec 2016 02:19:08 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T9291' created Message-ID: <20161217021908.6DAE43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T9291 Referencing: bd03f55ded59a0ba6da59e5c4a04f648d670f261 From git at git.haskell.org Sat Dec 17 02:19:12 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Dec 2016 02:19:12 +0000 (UTC) Subject: [commit: ghc] wip/T9291: Add a CSE pass to Stg (#9291) (bd03f55) Message-ID: <20161217021912.8ED813A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9291 Link : http://ghc.haskell.org/trac/ghc/changeset/bd03f55ded59a0ba6da59e5c4a04f648d670f261/ghc >--------------------------------------------------------------- commit bd03f55ded59a0ba6da59e5c4a04f648d670f261 Author: Joachim Breitner Date: Thu Dec 15 10:57:43 2016 -0800 Add a CSE pass to Stg (#9291) This CSE pass only targets data constructor applications. This is probably the best we can do, as function calls and primitive operations might have side-effects. Introduces the flag -fstg-cse. >--------------------------------------------------------------- bd03f55ded59a0ba6da59e5c4a04f648d670f261 compiler/coreSyn/TrieMap.hs | 6 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 3 + compiler/simplStg/SimplStg.hs | 30 +-- compiler/simplStg/StgCse.hs | 229 +++++++++++++++++++++ testsuite/tests/{ado => simplStg}/Makefile | 0 .../should_run}/Makefile | 0 testsuite/tests/simplStg/should_run/T9291.hs | 27 +++ .../should_run/T9291.stdout} | 1 - testsuite/tests/simplStg/should_run/all.T | 12 ++ 10 files changed, 293 insertions(+), 16 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc bd03f55ded59a0ba6da59e5c4a04f648d670f261 From git at git.haskell.org Sat Dec 17 16:53:08 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Dec 2016 16:53:08 +0000 (UTC) Subject: [commit: ghc] master: UNREG: include CCS_OVERHEAD to STG (2fa00f5) Message-ID: <20161217165308.D138D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2fa00f5b22dd9ea39eb1f5c9b52bbdbca0a37925/ghc >--------------------------------------------------------------- commit 2fa00f5b22dd9ea39eb1f5c9b52bbdbca0a37925 Author: Sergei Trofimovich Date: Sat Dec 17 13:25:43 2016 +0000 UNREG: include CCS_OVERHEAD to STG Commit 394231b301efb6b56654b0a480ab794fe3b7e4db aded CCS_OVERHEAD annotation to 'rts/Apply.cmm'. Before the change CCS_OVERHEAD was used only in C code. The change exports CCS_OVERHEAD to STG. Fixes UNREG build failure: rts_dist_HC rts/dist/build/Apply.p_o /tmp/ghc29563_0/ghc_4.hc: In function 'cm_entry': /tmp/ghc29563_0/ghc_4.hc:73:13: error: error: 'CCS_OVERHEAD' undeclared (first use in this function) *((P_)((W_)&CCS_OVERHEAD+72)) = ... ^~~~~~~~~~~~ Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 2fa00f5b22dd9ea39eb1f5c9b52bbdbca0a37925 includes/stg/MiscClosures.h | 1 + 1 file changed, 1 insertion(+) diff --git a/includes/stg/MiscClosures.h b/includes/stg/MiscClosures.h index 65562b2..b3f9a69 100644 --- a/includes/stg/MiscClosures.h +++ b/includes/stg/MiscClosures.h @@ -512,6 +512,7 @@ extern unsigned int RTS_VAR(era); extern unsigned int RTS_VAR(entering_PAP); extern StgWord RTS_VAR(CC_LIST); /* registered CC list */ extern StgWord RTS_VAR(CCS_LIST); /* registered CCS list */ +extern StgWord CCS_OVERHEAD[]; extern StgWord CCS_SYSTEM[]; extern unsigned int RTS_VAR(CC_ID); /* global ids */ extern unsigned int RTS_VAR(CCS_ID); From git at git.haskell.org Sat Dec 17 16:53:11 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Dec 2016 16:53:11 +0000 (UTC) Subject: [commit: ghc] master: revert '-Wl' prefixing to *_LD_OPTS (a6657bd) Message-ID: <20161217165311.93BB53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a6657bd0d6b9949098021d89ed3cd8a943bdd3b6/ghc >--------------------------------------------------------------- commit a6657bd0d6b9949098021d89ed3cd8a943bdd3b6 Author: Sergei Trofimovich Date: Sat Dec 17 13:30:41 2016 +0000 revert '-Wl' prefixing to *_LD_OPTS This reverts f48f5a9ebf384e1e157b7b413e1d779f4289ddd2 The prefixing does not work as comma is stripped by $(addprefix) macro: The following call $$(addprefix -optl-Wl, $$($1_$2_$3_ALL_LD_OPTS)) prefixes options with "-optl-Wl" not with "-optl-Wl," The simplest breakage can be seen by adding SRC_LD_OPTS += -O1 to mk/build.mk: : error: Warning: Couldn't figure out linker information! Make sure you're using GNU ld, GNU gold or the built in OS X linker, etc. gcc: error: unrecognized command line option '-Wl-O1' Another problem with original change is loss of ability to pass options to gcc as a linker driver, for example: SRC_LD_OPTS += -flto Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- a6657bd0d6b9949098021d89ed3cd8a943bdd3b6 rules/distdir-way-opts.mk | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rules/distdir-way-opts.mk b/rules/distdir-way-opts.mk index 602e6eb..6ae9807 100644 --- a/rules/distdir-way-opts.mk +++ b/rules/distdir-way-opts.mk @@ -207,7 +207,7 @@ $1_$2_$3_ALL_LD_OPTS = \ # Options for passing to GHC when we use it for linking $1_$2_$3_GHC_LD_OPTS = \ - $$(addprefix -optl-Wl, $$($1_$2_$3_ALL_LD_OPTS)) \ + $$(addprefix -optl, $$($1_$2_$3_ALL_LD_OPTS)) \ $$($1_$2_$3_MOST_HC_OPTS) $1_$2_$3_ALL_AS_OPTS = \ From git at git.haskell.org Sat Dec 17 16:53:14 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Dec 2016 16:53:14 +0000 (UTC) Subject: [commit: ghc] master: rts/Compact.cmm: fix UNREG build failure (c480860) Message-ID: <20161217165314.4ECF13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c4808602124577217dbd39576c120a77f923ca6f/ghc >--------------------------------------------------------------- commit c4808602124577217dbd39576c120a77f923ca6f Author: Sergei Trofimovich Date: Sat Dec 17 13:39:18 2016 +0000 rts/Compact.cmm: fix UNREG build failure The change does the following: - Add explicit declaration of exception closures from base. C backend needs those symbols to be visible. - Reorder cmm functions in use order. Again C backend needs symbol declaration/definition before use. even for module-local cmm functions. Fixes the following build failure: rts_dist_HC rts/dist/build/Compact.o In file included from /tmp/ghc3348_0/ghc_4.hc:3:0: error: /tmp/ghc3348_0/ghc_4.hc: In function 'stg_compactAddWithSharingzh': /tmp/ghc3348_0/ghc_4.hc:27:11: error: error: 'stg_compactAddWorkerzh' undeclared (first use in this function) JMP_((W_)&stg_compactAddWorkerzh); ^ ... /tmp/ghc3348_0/ghc_4.hc:230:13: error: error: 'base_GHCziIOziException_cannotCompactMutable_closure' undeclared (first use in this function) R1.w = (W_)&base_GHCziIOziException_cannotCompactMutable_closure; ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- c4808602124577217dbd39576c120a77f923ca6f rts/Compact.cmm | 109 ++++++++++++++++++++++++++++---------------------------- 1 file changed, 55 insertions(+), 54 deletions(-) diff --git a/rts/Compact.cmm b/rts/Compact.cmm index fe54d2a..0b98f39 100644 --- a/rts/Compact.cmm +++ b/rts/Compact.cmm @@ -10,60 +10,9 @@ #include "Cmm.h" #include "sm/ShouldCompact.h" - -// -// compactAddWithSharing# -// :: State# RealWorld -// -> Compact# -// -> a -// -> (# State# RealWorld, a #) -// -stg_compactAddWithSharingzh (P_ compact, P_ p) -{ - W_ hash; - ASSERT(StgCompactNFData_hash(compact) == NULL); - (hash) = ccall allocHashTable(); - StgCompactNFData_hash(compact) = hash; - - // Note [compactAddWorker result] - // - // compactAddWorker needs somewhere to store the result - this is - // so that it can be tail-recursive. It must be an address that - // doesn't move during GC, so we can't use heap or stack. - // Therefore we have a special field in the StgCompactNFData - // object to hold the final result of compaction. - W_ pp; - pp = compact + SIZEOF_StgHeader + OFFSET_StgCompactNFData_result; - call stg_compactAddWorkerzh(compact, p, pp); - ccall freeHashTable(StgCompactNFData_hash(compact), NULL); - StgCompactNFData_hash(compact) = NULL; -#ifdef DEBUG - ccall verifyCompact(compact); -#endif - return (P_[pp]); -} - - -// -// compactAdd# -// :: State# RealWorld -// -> Compact# -// -> a -// -> (# State# RealWorld, a #) -// -stg_compactAddzh (P_ compact, P_ p) -{ - ASSERT(StgCompactNFData_hash(compact) == NULL); - - W_ pp; // See Note [compactAddWorker result] - pp = compact + SIZEOF_StgHeader + OFFSET_StgCompactNFData_result; - call stg_compactAddWorkerzh(compact, p, pp); -#ifdef DEBUG - ccall verifyCompact(compact); -#endif - return (P_[pp]); -} - +import CLOSURE base_GHCziIOziException_cannotCompactFunction_closure; +import CLOSURE base_GHCziIOziException_cannotCompactMutable_closure; +import CLOSURE base_GHCziIOziException_cannotCompactPinned_closure; // // Allocate space for a new object in the compact region. We first try @@ -310,6 +259,58 @@ eval: ccall barf("stg_compactWorkerzh"); } +// +// compactAddWithSharing# +// :: State# RealWorld +// -> Compact# +// -> a +// -> (# State# RealWorld, a #) +// +stg_compactAddWithSharingzh (P_ compact, P_ p) +{ + W_ hash; + ASSERT(StgCompactNFData_hash(compact) == NULL); + (hash) = ccall allocHashTable(); + StgCompactNFData_hash(compact) = hash; + + // Note [compactAddWorker result] + // + // compactAddWorker needs somewhere to store the result - this is + // so that it can be tail-recursive. It must be an address that + // doesn't move during GC, so we can't use heap or stack. + // Therefore we have a special field in the StgCompactNFData + // object to hold the final result of compaction. + W_ pp; + pp = compact + SIZEOF_StgHeader + OFFSET_StgCompactNFData_result; + call stg_compactAddWorkerzh(compact, p, pp); + ccall freeHashTable(StgCompactNFData_hash(compact), NULL); + StgCompactNFData_hash(compact) = NULL; +#ifdef DEBUG + ccall verifyCompact(compact); +#endif + return (P_[pp]); +} + +// +// compactAdd# +// :: State# RealWorld +// -> Compact# +// -> a +// -> (# State# RealWorld, a #) +// +stg_compactAddzh (P_ compact, P_ p) +{ + ASSERT(StgCompactNFData_hash(compact) == NULL); + + W_ pp; // See Note [compactAddWorker result] + pp = compact + SIZEOF_StgHeader + OFFSET_StgCompactNFData_result; + call stg_compactAddWorkerzh(compact, p, pp); +#ifdef DEBUG + ccall verifyCompact(compact); +#endif + return (P_[pp]); +} + stg_compactSizzezh (P_ compact) { return (StgCompactNFData_totalW(compact) * SIZEOF_W); From git at git.haskell.org Sat Dec 17 19:21:56 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Dec 2016 19:21:56 +0000 (UTC) Subject: [commit: ghc] master: Fix Pretty printer tests on Windows (d88efb7) Message-ID: <20161217192156.84E3B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d88efb7048160c3031eadb4f3b729e9fe406414d/ghc >--------------------------------------------------------------- commit d88efb7048160c3031eadb4f3b729e9fe406414d Author: Tamar Christina Date: Sat Dec 17 16:40:11 2016 +0000 Fix Pretty printer tests on Windows Summary: D2752 added some tests which escapes string literals. This means newlines are converted before they get normalized by the IO functions. So on Windows \r\n would be in the output while \n was expected. Test Plan: make test -C testsuite/tests/printer Reviewers: austin, bgamari, alanz Reviewed By: alanz Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2873 GHC Trac Issues: #3384 >--------------------------------------------------------------- d88efb7048160c3031eadb4f3b729e9fe406414d utils/check-ppr/Main.hs | 15 ++++++++++----- 1 file changed, 10 insertions(+), 5 deletions(-) diff --git a/utils/check-ppr/Main.hs b/utils/check-ppr/Main.hs index 8c93769..c9fac7d 100644 --- a/utils/check-ppr/Main.hs +++ b/utils/check-ppr/Main.hs @@ -132,10 +132,10 @@ showAstData n = space "" = "" space s = ' ':s indent i = "\n" ++ replicate i ' ' - string = show :: String -> String - fastString = ("{FastString: "++) . (++"}") . show + string = normalize_newlines . show :: String -> String + fastString = ("{FastString: "++) . (++"}") . normalize_newlines . show :: FastString -> String - bytestring = show :: B.ByteString -> String + bytestring = normalize_newlines . show :: B.ByteString -> String list l = indent n ++ "[" ++ intercalate "," (map (showAstData (n+1)) l) ++ "]" @@ -179,11 +179,16 @@ showAstData n = ++ showAstData (n+1) a ++ ")" +normalize_newlines :: String -> String +normalize_newlines ('\\':'r':'\\':'n':xs) = '\\':'n':normalize_newlines xs +normalize_newlines (x:xs) = x:normalize_newlines xs +normalize_newlines [] = [] + showSDoc_ :: SDoc -> String -showSDoc_ = showSDoc unsafeGlobalDynFlags +showSDoc_ = normalize_newlines . showSDoc unsafeGlobalDynFlags showSDocDebug_ :: SDoc -> String -showSDocDebug_ = showSDocDebug unsafeGlobalDynFlags +showSDocDebug_ = normalize_newlines . showSDocDebug unsafeGlobalDynFlags -- --------------------------------------------------------------------- From git at git.haskell.org Sat Dec 17 21:33:47 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Dec 2016 21:33:47 +0000 (UTC) Subject: [commit: ghc] wip/T9291: Add a CSE pass to Stg (#9291) (248aa50) Message-ID: <20161217213347.B48513A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9291 Link : http://ghc.haskell.org/trac/ghc/changeset/248aa5021846845c47ae493be70e555358b1ccbe/ghc >--------------------------------------------------------------- commit 248aa5021846845c47ae493be70e555358b1ccbe Author: Joachim Breitner Date: Thu Dec 15 10:57:43 2016 -0800 Add a CSE pass to Stg (#9291) This CSE pass only targets data constructor applications. This is probably the best we can do, as function calls and primitive operations might have side-effects. Introduces the flag -fstg-cse, enabled by default with -O. >--------------------------------------------------------------- 248aa5021846845c47ae493be70e555358b1ccbe compiler/coreSyn/TrieMap.hs | 6 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 3 + compiler/simplStg/SimplStg.hs | 30 +- compiler/simplStg/StgCse.hs | 357 +++++++++++++++++++++ docs/users_guide/using-optimisation.rst | 8 + testsuite/tests/{ado => simplStg}/Makefile | 0 .../should_run}/Makefile | 0 testsuite/tests/simplStg/should_run/T9291.hs | 27 ++ .../should_run/T9291.stdout} | 1 - testsuite/tests/simplStg/should_run/all.T | 12 + 11 files changed, 429 insertions(+), 16 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 248aa5021846845c47ae493be70e555358b1ccbe From git at git.haskell.org Sat Dec 17 22:04:10 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Dec 2016 22:04:10 +0000 (UTC) Subject: [commit: ghc] wip/T9291: Add a CSE pass to Stg (#9291) (c33f5af) Message-ID: <20161217220410.A7B1B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9291 Link : http://ghc.haskell.org/trac/ghc/changeset/c33f5af6b6ffb7a3cf61cb7f987bc7cd45bf7559/ghc >--------------------------------------------------------------- commit c33f5af6b6ffb7a3cf61cb7f987bc7cd45bf7559 Author: Joachim Breitner Date: Thu Dec 15 10:57:43 2016 -0800 Add a CSE pass to Stg (#9291) This CSE pass only targets data constructor applications. This is probably the best we can do, as function calls and primitive operations might have side-effects. Introduces the flag -fstg-cse, enabled by default with -O. >--------------------------------------------------------------- c33f5af6b6ffb7a3cf61cb7f987bc7cd45bf7559 compiler/coreSyn/TrieMap.hs | 6 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 3 + compiler/simplStg/SimplStg.hs | 30 +- compiler/simplStg/StgCse.hs | 357 +++++++++++++++++++++ docs/users_guide/using-optimisation.rst | 8 + testsuite/tests/{ado => simplStg}/Makefile | 0 .../should_run}/Makefile | 0 testsuite/tests/simplStg/should_run/T9291.hs | 27 ++ .../should_run/T9291.stdout} | 1 - testsuite/tests/simplStg/should_run/all.T | 12 + 11 files changed, 429 insertions(+), 16 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c33f5af6b6ffb7a3cf61cb7f987bc7cd45bf7559 From git at git.haskell.org Sat Dec 17 22:04:13 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Dec 2016 22:04:13 +0000 (UTC) Subject: [commit: ghc] wip/T9291's head updated: Add a CSE pass to Stg (#9291) (c33f5af) Message-ID: <20161217220413.AE6DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T9291' now includes: 9c39e09 Switch to LLVM version 3.9 94d1221 Add missing SMP symbols to RT linker. d328abc Spelling in comment only 3bd1dd4 Add Data instance for Const 4b72f85 Optimise whole module exports 6ad94d8 Updated code comment regarding EquationInfo. Trac #12856 ea37b83 A few typos in comments 5bce207 testsuite: Add test for #12855 926469f testsuite: Add test for #12024 b98dbdf testsuite: Add (still broken) testcase for #12447 e7ec521 testsuite: Add (still failing) testcase for #12550 ea76a21 add ieee754 next* functions to math_funs 514acfe Implement fine-grained `-Werror=...` facility 4c0dc76 Ignore Hadrian build products. 7e4b611 Make transformers upstream repository location consistent with others 1399c8b ghc/hschooks.c: Fix include path of Rts.h f430253 Allow to unregister threadWaitReadSTM action. 14ac372 Collect wildcards in sum types during renaming (#12711) d081fcf Make quoting and reification return the same types 9a431e5 Make a panic into an ASSERT 0476a64 Fix a bug in mk_superclasses_of f04f118 Comments only in TcType 0123efd Add elemDVarEnv 1eec1f2 Another major constraint-solver refactoring 18d0bdd Allow TyVars in TcTypes 4431e48 Remove redundant kind check 90a65ad Perf improvements in T6048, T10547 e319466 Typos in comments c1b4b76 Fix a name-space problem with promotion f0f4682 Test Trac #12867 83a952d Test Trac #12845 a5a3926 Kill off ifaceTyVarsOfType bc35c3f Use 'v' instead of 'tpl' for template vars edbe831 Use TyVars in a DFunUnfolding 12eff23 Use TyVars in PatSyns 5f349fe Improve pretty-printing of types eb55ec2 Refactor functional dependencies a bit 1bfff60 Fix inference of partial signatures 086b483 A tiny bit more tc tracing f8c966c Be a bit more selective about improvement 6ec2304 Fix an long-standing bug in OccurAnal 5238842 Typos in comments only [ci skip] 605af54 Test Trac #12776 27a6bdf Test Trac #12885 3aa9368 Comments only (related to #12789) abd4a4c Make note of #12881 in 8.0.2 release notes f8c8de8 Zonk the free tvs of a RULE lhs to TyVars e755930 Typos in comments 36e3622 Store string as parsed in SourceText for CImport 1732d7a Define thread primitives if they're supported. 30cecae users_guide: Bring 8.0.2 release notes up-to-date with ghc-8.0 branch f1fc8cb Make diagnostics slightly more colorful 52222f9b Detect color support da5a61e Minor cleanup of foldRegs{Used,Defd} 2d99da0 testsuite: Mention CLEANUP option in README 3ec8563 Replace -fshow-source-paths with -fhide-source-paths c2268ba Refactor Pattern Match Checker to use ListT 6845087 Purge GHC of literate Perl 4d4e7a5 Use newBlockId instead of newLabelC 7753273 AsmCodeGen: Refactor worker in cmmNativeGens 6d5c2e7 NCGMonad: Add MonadUnique NatM instance eaed140 OrdList: Add Foldable, Traversable instances fe3748b testsuite: Bump haddock.compiler allocations 795f8bd hschooks.c: Ensure correct header file is included 6f7ed1e Make globals use sharedCAF 56d7451 Fix type of GarbageCollect declaration 428e152 Use C99's bool 758b81d rts: Add missing #include 23dc6c4 Remove most functions from cmm/BlockId b92f8e3 Added Eq1, Ord1, Read1 and Show1 instances for NonEmpty 679ccd1 Hoopl/Dataflow: use block-oriented interface 0ce59be Fix testsuite threading, timeout, encoding and performance issues on Windows dd9ba50 Update test output for Windows 605bb9b testsuite: Use python3 by default 20c0614 Update Mingw-w64 bindist for Windows ef37580 Fix windows validate. be8a47f Tweaks to grammar and such. 03766cd Rename RuntimeRepPolymorphism to LevityPolymorphism e2330b6 Revert "Make globals use sharedCAF" c2a2911 Revert "Fix windows validate." 6c54fa5 testsuite: Add another testcase for #11821 0200ded Fix typo in functional dependencies doc f48f5a9e Ensure flags destined for ld are properly passed 514c01e Levity polymorphic expressions mustn't be floated-out in let-bindings. a452c6e Make note of #12907 in 8.0.2 release notes 0ac5e0c rts: Fix type of bool literal 7214e92 testsuite: Remove Unicode literals from driver 6576bf8 rts: Ensure we always give MADV_DONTNEED a chance in osDecommitMemory 0f37550 Typos in comments a934e25 testsuite: Actually update haddock.compiler allocations 7fafb84 testsuite/conc059: Don't attempt to use stdcall where it isn't supported 747e77c Fix naming of the native latin1 encodings ddc271e Travis: Add dependency on python3 27731f1 Note Trac #12141 in mk/build.mk.sample f46369b fdReady: use poll() instead of select() 895a131 Install toplevel handler inside fork. 2350906 Maintain in-scope set in deeply_instantiate (fixes #12549). eb6f673 8.2.1-notes.rst: tweak binutils version 90c5af4 core-spec: Fix S_MatchData 517d03e Fix an asymptotic bug in the occurrence analyser 6305674 Fix used-variable calculation (Trac #12548) e912310 Use isFamFreeTyCon now we have it 3e3f7c2 Test Trac #12925 847d229 Color output is wreaking havoc on test results b82f71b Fix x86 Windows build and testsuite eec02ab Give concrete example for #12784 in 8.0.2 release notes 24e6594 Overhaul GC stats 19ae142 Mark rn017 and T7672 as expect_broken(#12930) with -DDEBUG 6e4188a Fix unsafe usage of `is_iloc` selector in Ord instance for ImportSpec eafa06d Revert "Mark rn017 and T7672 as expect_broken(#12930) with -DDEBUG" b7e88ee Reduce the size of string literals in binaries. 41ec722d Test Trac #12919 39143a4 Mark T9577 as broken on Darwin due to #12937 4dd6b37 Really mark T9577 as broken 7036fde Overhaul of Compact Regions (#12455) c02aeb5 Ignore output for compact_gc: sizes change when profiling 5aa9c75 Fix the test with -O 9043a40 Fix crashes in hash table scanning with THREADED_RTS d70d452 rts: Use pthread itimer implementation on Darwin 83d69dc Don't barf() on failures in loadArchive() 499e438 Add HsSyn prettyprinter tests 58d78dc Fix pretty printer test to nog generate stdout 9bcc4e3 Remove stray commented out line in all.T c5fbbac Ignore stderr of all printer tests 62332f3 Setup tcg_imports earlier during signature matching, so orphans are visible. 617d57d Reduce qualification in error messages from signature matching. 58c290a hschooks.c: Fix long line 5063edb arclint: Lint cabal files c766d53 rts/linker: Fix LoadArchive build on Windows 6889400 testsuite: Add test for #10249 1e5b7d7 Update Windows GCC driver. 55361b3 nativeGen: Fix string merging on Windows 2bb099e BlockId: remove BlockMap and BlockSet synonyms 6da6253 rts/PosixSource.h: Define __USE_MINGW_ANSI_STDIO on Windows f65ff2c Disambiguate reified closed type family kinds in TH 61932cd Bump haddock submodule d3b546b Scrutinee Constant Folding cee72d5 Disable colors unless printing to stderr 1c296c0c Export `warningGroups' and `warningHierarchies' 62418b8 Mark T12903 as broken on OS X 90fae01 Fix LLVM TBAA metadata 2823492 NCG: Implement trivColorable for PowerPC 64-bit ca593c7 testsuite: make tests respond to SIGINT properly d1df8d1 Ensure each test inherits the TEST_HC_OPTS 5349d64 Rename TH constructors for deriving strategies 24a4fe2 testsuite: Mark prog003 as broken on Windows 2618090 testsuite: Fix syntax error in rts/all.T 17ac9b1 rts: Provide _lock_file in symbol table on Windows 0ac5a00 Add `_unlock_file` to RTS symbols 490b942 Automate GCC driver wrapper c3c7024 Make globals use sharedCAF 818e027 Refactor pruning of implication constraints f1036ad Make dropDerivedSimples restore [WD] constraints 6720376 Disable T12903 due to flakiness d03dd23 Fix a long-standing bug in CSE bc3d37d Float unboxed expressions by boxing 8f6d241 Add infix flag for class and data declarations 24f6bec Sanity check if we pick up an hsig file without -instantiated-with. db23ccf Fix recompilation detection when set of signatures to merge changes. f723ba2 Revert "Float unboxed expressions by boxing" cc2e3ec base: Make raw buffer IO operations more strict cb582b6 Don't have CPP macros expanding to 'defined'. 9cb4a13 Fix Win32 x86 build validation after D2756 aa123f4 Fix testcase T12903 on OS X 7031704 print * in unicode correctly (fixes #12550) 8ec864d Fix pretty printing of top level SCC pragmas 9c9a222 Load orphan interfaces before checking if module implements signature 26ce99c Fix typo in users' guide 52c5e55 mk/config.mk.in: enable SMP on ARMv7+ (Trac #12981) 0c3341b Show constraints when reporting typed holes 6f7d827 Reset FPU precision back to MSVCRT defaults 8b2e588 Adds llvm-prof flavour 6370a56 Build terminfo on iOS. 3c7cf18 Fix pprCLabel on platforms without native codegen. be5384c testsuite: Mark T9577 as broken due to #12965 27287c8 procPointAnalysis doesn't need UniqSM fe5d68a Add entry to .gitignore to for __.SYMDEF_SORTED 9550b8d Make unboxedTuple{Type,Data}Name support 0- and 1-tuples 2940a61 testsuite: Specify expected allocations of T12877 for Windows 5c76f83 check-ppr: Add a --dump flag to aid in debugging 394231b Fix cost-centre-stacks bug (#5654) 1ec632f Fix pretty printing of MINIMAL signatures 503219e Warn about missing instance methods that start with an underscore d398162 testsuite: Separate out Windows results for T5205 4d683fa base: Bump version to 4.10.0.0 8f0546b testsuite: Add test for #12971 0cad52d testsuite: Mark T10294 as fixed 81c4956 testsuite: Add test for #12966 cd4b202 array: Check for integer overflow during allocation 0d213c1 UniqSupply: Use full range of machine word ffc2327 base: Add more POSIX types (fixes #12795) 6fecb2a Verify that known-key uniques fit in interface file ed4cf03 Typos in comments 13c1fc4 DynFlags: Rip out remnants of WarnContextQuantification c889df8 Packages: Kill unused UnitId argument to isDllName 5bf344b CLabel: Kill redundant UnitId argument from labelDynamic 222e99d Make up a module name for c-- files 4026b45 Fix string merging with -split-sections 8f71d95 Enable split sections by default where possible c8ed1bd testsuite: Add test for #12993 2fa00f5 UNREG: include CCS_OVERHEAD to STG a6657bd revert '-Wl' prefixing to *_LD_OPTS c480860 rts/Compact.cmm: fix UNREG build failure d88efb7 Fix Pretty printer tests on Windows c33f5af Add a CSE pass to Stg (#9291) From git at git.haskell.org Sat Dec 17 22:35:39 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Dec 2016 22:35:39 +0000 (UTC) Subject: [commit: ghc] master: Revert "Do not init record accessors as exported" (0af959b) Message-ID: <20161217223539.71E933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0af959b1999b48f3b8e6c47184b6f8c80b4c452d/ghc >--------------------------------------------------------------- commit 0af959b1999b48f3b8e6c47184b6f8c80b4c452d Author: Ben Gamari Date: Sat Dec 17 11:53:59 2016 -0500 Revert "Do not init record accessors as exported" This reverts commit 3a00ff92a3ee66c096b85b180d247d1a471a6b6e due to #12993 >--------------------------------------------------------------- 0af959b1999b48f3b8e6c47184b6f8c80b4c452d compiler/basicTypes/Id.hs | 7 ------- compiler/deSugar/Desugar.hs | 5 +---- compiler/typecheck/TcTyDecls.hs | 7 +------ testsuite/tests/th/all.T | 3 +-- 4 files changed, 3 insertions(+), 19 deletions(-) diff --git a/compiler/basicTypes/Id.hs b/compiler/basicTypes/Id.hs index b2be2c0..1b84acd 100644 --- a/compiler/basicTypes/Id.hs +++ b/compiler/basicTypes/Id.hs @@ -33,7 +33,6 @@ module Id ( mkLocalId, mkLocalCoVar, mkLocalIdOrCoVar, mkLocalIdOrCoVarWithInfo, mkLocalIdWithInfo, mkExportedLocalId, mkExportedVanillaId, - mkNonExportedLocalId, mkSysLocal, mkSysLocalM, mkSysLocalOrCoVar, mkSysLocalOrCoVarM, mkUserLocal, mkUserLocalOrCoVar, mkTemplateLocals, mkTemplateLocalsNum, mkTemplateLocal, @@ -286,12 +285,6 @@ mkExportedLocalId :: IdDetails -> Name -> Type -> Id mkExportedLocalId details name ty = Var.mkExportedLocalVar details name ty vanillaIdInfo -- Note [Free type variables] --- | Create a local 'Id' that is marked as not-exported. --- These may be removed as dead code. -mkNonExportedLocalId :: IdDetails -> Name -> Type -> Id -mkNonExportedLocalId details name ty = - Var.mkLocalVar details name ty vanillaIdInfo - mkExportedVanillaId :: Name -> Type -> Id mkExportedVanillaId name ty = Var.mkExportedLocalVar VanillaId name ty vanillaIdInfo -- Note [Free type variables] diff --git a/compiler/deSugar/Desugar.hs b/compiler/deSugar/Desugar.hs index e73f12f..1e117b3 100644 --- a/compiler/deSugar/Desugar.hs +++ b/compiler/deSugar/Desugar.hs @@ -304,10 +304,7 @@ deSugar hsc_env (text "Desugar"<+>brackets (ppr mod)) (const ()) $ do { -- Desugar the program - ; let export_set = - -- Used to be 'availsToNameSet', but we now export selectors - -- only when necessary. See #12125. - availsToNameSetWithSelectors exports + ; let export_set = availsToNameSet exports target = hscTarget dflags hpcInfo = emptyHpcInfo other_hpc_info diff --git a/compiler/typecheck/TcTyDecls.hs b/compiler/typecheck/TcTyDecls.hs index e8046c7..ae9f16d 100644 --- a/compiler/typecheck/TcTyDecls.hs +++ b/compiler/typecheck/TcTyDecls.hs @@ -806,12 +806,7 @@ mkOneRecordSelector all_cons idDetails fl lbl = flLabel fl sel_name = flSelector fl - sel_id = - -- Do not mark record selectors as exported to avoid keeping these Ids - -- alive unnecessarily. See #12125. Selectors are now marked as exported - -- when necessary by desugarer ('Desugar.addExportFlagsAndRules', also see - -- uses of 'availsToNameSetWithSelectors' in 'Desugar.hs'). - mkNonExportedLocalId rec_details sel_name sel_ty + sel_id = mkExportedLocalId rec_details sel_name sel_ty rec_details = RecSelId { sel_tycon = idDetails, sel_naughty = is_naughty } -- Find a representative constructor, con1 diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index bb11528..ce4c5f5 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -445,5 +445,4 @@ test('T12788', extra_clean(['T12788_Lib.hi', 'T12788_Lib.o']), multimod_compile_fail, ['T12788.hs', '-v0 ' + config.ghc_th_way_flags]) test('T12977', normal, compile, ['-v0']) -test('T12993', expect_broken(12993), multimod_compile, - ['T12993.hs', '-v0']) \ No newline at end of file +test('T12993', normal, multimod_compile, ['T12993.hs', '-v0']) \ No newline at end of file From git at git.haskell.org Sat Dec 17 22:51:13 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Dec 2016 22:51:13 +0000 (UTC) Subject: [commit: ghc] master: fix OpenBSD linkage (wxneeded) (87c3b1d) Message-ID: <20161217225113.A61993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/87c3b1d4395c3d4fc7a5272717c48f3f525da959/ghc >--------------------------------------------------------------- commit 87c3b1d4395c3d4fc7a5272717c48f3f525da959 Author: Sergei Trofimovich Date: Sat Dec 17 20:25:19 2016 +0000 fix OpenBSD linkage (wxneeded) There is two types of options passed directly to 'ld' (and not to 'gcc' driver): - CONF_LD_LINKER_OPTS_STAGE$4 - EXTRA_LD_OPTS This changedoes two things: - split 'EXTRA_LD_OPTS' into two variables: - EXTRA_LD_OPTS (accepts 'gcc' wrapper options) - EXTRA_LD_LINKER_OPTS (accepts raw 'ld' options) - wraps all LD_LINKER options as '-Wl,' when passed to 'gcc' driver. Fixes https://phabricator.haskell.org/D2776 Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 87c3b1d4395c3d4fc7a5272717c48f3f525da959 aclocal.m4 | 2 +- rules/build-package-way.mk | 2 +- rules/distdir-way-opts.mk | 5 +++-- 3 files changed, 5 insertions(+), 4 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 5d39570..4673ac0 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -658,7 +658,7 @@ AC_DEFUN([FPTOOLS_SET_C_LD_FLAGS], x86_64-*-openbsd*) # We need -z wxneeded at least to link ghc-stage2 to workaround # W^X issue in GHCi on OpenBSD current (as of Aug 2016) - $3="$$3 -Wl,-zwxneeded" + $3="$$3 -Wl,-z,wxneeded" $4="$$4 -z wxneeded" ;; diff --git a/rules/build-package-way.mk b/rules/build-package-way.mk index 905b7f0..8f61a35 100644 --- a/rules/build-package-way.mk +++ b/rules/build-package-way.mk @@ -155,7 +155,7 @@ BINDIST_LIBS += $$($1_$2_GHCI_LIB) endif endif $$($1_$2_GHCI_LIB) : $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS) $$($1_$2_LD_SCRIPT) - $$(call cmd,LD) $$(CONF_LD_LINKER_OPTS_STAGE$4) -r $$(if $$($1_$2_LD_SCRIPT),-T $$($1_$2_LD_SCRIPT)) -o $$@ $$(EXTRA_LD_OPTS) $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS) + $$(call cmd,LD) $$(CONF_LD_LINKER_OPTS_STAGE$4) -r $$(if $$($1_$2_LD_SCRIPT),-T $$($1_$2_LD_SCRIPT)) -o $$@ $$(EXTRA_LD_LINKER_OPTS) $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS) ifeq "$$($1_$2_BUILD_GHCI_LIB)" "YES" # Don't bother making ghci libs for bootstrapping packages diff --git a/rules/distdir-way-opts.mk b/rules/distdir-way-opts.mk index 6ae9807..62a1451 100644 --- a/rules/distdir-way-opts.mk +++ b/rules/distdir-way-opts.mk @@ -196,14 +196,15 @@ $1_$2_$3_GHC_CC_OPTS = \ $$(addprefix -optc, $$($1_$2_$3_ALL_CC_OPTS)) \ $$($1_$2_$3_MOST_HC_OPTS) -# Options for passing to plain ld +# Options for passing to gcc for linking $1_$2_$3_ALL_LD_OPTS = \ $$(WAY_$3_LD_OPTS) \ $$($1_$2_DIST_LD_OPTS) \ $$($1_$2_$3_LD_OPTS) \ $$($1_$2_EXTRA_LD_OPTS) \ $$(EXTRA_LD_OPTS) \ - $$(CONF_LD_LINKER_OPTS_STAGE$4) + $$(foreach o,$$(EXTRA_LD_LINKER_OPTS),-optl-Wl$$(comma)$$o) \ + $$(foreach o,$$(CONF_LD_LINKER_OPTS_STAGE$4),-optl-Wl$$(comma)$$o) # Options for passing to GHC when we use it for linking $1_$2_$3_GHC_LD_OPTS = \ From git at git.haskell.org Sat Dec 17 22:51:16 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Dec 2016 22:51:16 +0000 (UTC) Subject: [commit: ghc] master: utils/genargs: delete unused tool (6c816c5) Message-ID: <20161217225116.68B713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6c816c56c674221173e725b5718c8052dda0c8f4/ghc >--------------------------------------------------------------- commit 6c816c56c674221173e725b5718c8052dda0c8f4 Author: Sergei Trofimovich Date: Sat Dec 17 22:19:29 2016 +0000 utils/genargs: delete unused tool The tool was added in 2003 but never used at least in ghc tree. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 6c816c56c674221173e725b5718c8052dda0c8f4 utils/genargs/Makefile | 8 ------ utils/genargs/genargs.pl | 65 ------------------------------------------------ 2 files changed, 73 deletions(-) diff --git a/utils/genargs/Makefile b/utils/genargs/Makefile deleted file mode 100644 index 3c31e6a..0000000 --- a/utils/genargs/Makefile +++ /dev/null @@ -1,8 +0,0 @@ -comma = , -BAR= "-L\"foo bar\"" -FOO= $(patsubst %,$(comma)"%",$(BAR)) - -test: - @echo "$(FOO)" - @echo "$(BAR)" | $(PERL) genargs.pl -comma - @echo diff --git a/utils/genargs/genargs.pl b/utils/genargs/genargs.pl deleted file mode 100644 index 33dd2a0..0000000 --- a/utils/genargs/genargs.pl +++ /dev/null @@ -1,65 +0,0 @@ -#!/usr/bin/env perl - -use warnings; - -my $quote_open = 0; -my $quote_char = ''; -my $accum = ""; -my $once = 1; -my $c; - -# This program generates a partial Haskell list of Strings from -# words passed via stdin suitable for use in package.conf, e.g.: -# -# foo bar --> "foo", "bar" -# "foo bar" --> "foo bar" -# foo\"bar --> "foo\"bar" -# -# Invoking genargs.pl with -comma will print an initial comma if -# there's anything to print at all. -# -# Sample application in a Makefile: -# HSIFIED_EXTRA_LD_OPTS= `echo "$(EXTRA_LD_OPTS)" | $(PERL) genargs.pl` -# PACKAGE_CPP_OPTS += -DHSIFIED_EXTRA_LD_OPTS="$(HSIFIED_EXTRA_LD_OPTS)" - -sub printaccum { - if ($once) { - if ($ARGV[0] eq "-comma") { - print ", "; - } - } else { - print ", "; - } - $once=0; - print '"'; - print $accum; - print '"'; -} - -while ($c = getc) { - if ($quote_open) { - if ($c eq $quote_char) { - $quote_open = 0; - } elsif ($c eq '"') { - $accum .= '\"'; - } else { - $accum .= $c; - } - } else { - if (($c eq ' ') || ($c eq "\n")) { - if (!($accum eq "")) { - printaccum; - $accum = ""; - } - } elsif ($c eq "\\") { - $accum .= $c; - $c = getc; - $accum .= $c; - } elsif (($c eq '"') || ($c eq "\'")) { - $quote_open = 1; - $quote_char = $c; - } else { - $accum .= $c - } - } -} From git at git.haskell.org Sun Dec 18 01:01:58 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 01:01:58 +0000 (UTC) Subject: [commit: ghc] master: Reshuffle levity polymorphism checks. (8906e7b) Message-ID: <20161218010158.128CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8906e7b79a585039712034d9e88ca49f3cea6554/ghc >--------------------------------------------------------------- commit 8906e7b79a585039712034d9e88ca49f3cea6554 Author: Richard Eisenberg Date: Sat Dec 17 18:06:34 2016 -0500 Reshuffle levity polymorphism checks. Previously, GHC checked for bad levity polymorphism to the left of all arrows in data constructors. This was wrong, as reported in #12911 (where an example is also shown). The solution is to check each individual argument for bad levity polymorphism. Thus the check has been moved from TcValidity to TcTyClsDecls. A similar situation exists with pattern synonyms, also fixed here. This patch also nabs #12819 while I was in town. Test cases: typecheck/should_compile/T12911, patsyn/should_fail/T12819 Test Plan: ./validate Reviewers: simonpj, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2783 GHC Trac Issues: #12819, #12911 >--------------------------------------------------------------- 8906e7b79a585039712034d9e88ca49f3cea6554 compiler/typecheck/TcSigs.hs | 28 +++++++++++++++++----- compiler/typecheck/TcTyClsDecls.hs | 2 ++ compiler/typecheck/TcValidity.hs | 14 +---------- compiler/types/Type.hs | 5 ++-- testsuite/tests/patsyn/should_compile/T8968-2.hs | 2 +- .../tests/patsyn/should_compile/poly-export2.hs | 1 + testsuite/tests/patsyn/should_fail/T11010.hs | 2 +- testsuite/tests/patsyn/should_fail/T11039.hs | 3 +-- testsuite/tests/patsyn/should_fail/T11039a.hs | 2 +- testsuite/tests/patsyn/should_fail/T12819.hs | 9 +++++++ testsuite/tests/patsyn/should_fail/T12819.stderr | 3 +++ testsuite/tests/patsyn/should_fail/all.T | 1 + testsuite/tests/typecheck/should_compile/T12911.hs | 9 +++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 14 files changed, 56 insertions(+), 26 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8906e7b79a585039712034d9e88ca49f3cea6554 From git at git.haskell.org Sun Dec 18 01:02:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 01:02:01 +0000 (UTC) Subject: [commit: ghc] master: Windows: Improve terminal detection mechanism (3dbd2b0) Message-ID: <20161218010201.471AC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3dbd2b097aeb9217f4a7fc87e610e6983ebbce7b/ghc >--------------------------------------------------------------- commit 3dbd2b097aeb9217f4a7fc87e610e6983ebbce7b Author: Phil Ruffwind Date: Sat Dec 17 18:07:49 2016 -0500 Windows: Improve terminal detection mechanism The previous detection mechanism allowed environment variables (ANSICON, ConEmuANSI, TERM) to supersede the fact that the stderr is not a terminal, which is probably what led to color codes appearing in the stderr of the tests (see: 847d229346431483b99adcff12e46c7bf6af15da). This commit changes the detection mechanism to detect Cygwin/MSYS2 terminals in a more reliable manner, avoiding the use of environment variables entirely. Test Plan: validate Reviewers: Phyx, austin, erikd, bgamari Reviewed By: Phyx, bgamari Subscribers: RyanGlScott, thomie Differential Revision: https://phabricator.haskell.org/D2809 >--------------------------------------------------------------- 3dbd2b097aeb9217f4a7fc87e610e6983ebbce7b compiler/ghc.cabal.in | 1 + compiler/ghc.mk | 1 + compiler/main/DynFlags.hs | 100 +------------------------ compiler/main/SysTools/Terminal.hs | 150 +++++++++++++++++++++++++++++++++++++ 4 files changed, 154 insertions(+), 98 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3dbd2b097aeb9217f4a7fc87e610e6983ebbce7b From git at git.haskell.org Sun Dec 18 01:02:04 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 01:02:04 +0000 (UTC) Subject: [commit: ghc] master: Fix bug in previous fix for #5654 (2a02040) Message-ID: <20161218010204.01B213A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2a02040b2e23daa4f791afc290c33c9bbe3c620c/ghc >--------------------------------------------------------------- commit 2a02040b2e23daa4f791afc290c33c9bbe3c620c Author: Simon Marlow Date: Sat Dec 17 18:08:48 2016 -0500 Fix bug in previous fix for #5654 I forgot to account for BCOs, which have a different layout from functions. This caused crashes when using profiling with GHCi (via -fexternal-interpreter -prof), which unfortunately is not tested at all by validate, even when profiling is enabled. I'm going to add some testing that would have caught this in a separate patch. Test Plan: ``` cd nofib/spectral/puzzle && make NoFibWithGHCi=YES EXTRA_RUNTEST_OPTS='-fexternal-interpreter -prof' ``` New testsuite tests coming in a separate diff. Reviewers: niteria, austin, erikd, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2868 GHC Trac Issues: #5654 >--------------------------------------------------------------- 2a02040b2e23daa4f791afc290c33c9bbe3c620c rts/Apply.cmm | 13 +++++++++---- 1 file changed, 9 insertions(+), 4 deletions(-) diff --git a/rts/Apply.cmm b/rts/Apply.cmm index 3a73ce0..b18c347 100644 --- a/rts/Apply.cmm +++ b/rts/Apply.cmm @@ -57,6 +57,7 @@ stg_ap_0_fast ( P_ fun ) again: W_ info; W_ untaggedfun; + W_ arity; untaggedfun = UNTAG(fun); info = %INFO_PTR(untaggedfun); switch [INVALID_OBJECT .. N_CLOSURE_TYPES] @@ -68,6 +69,11 @@ again: fun = StgInd_indirectee(fun); goto again; } + case BCO: + { + arity = TO_W_(StgBCO_arity(untaggedfun)); + goto dofun; + } case FUN, FUN_1_0, @@ -75,9 +81,10 @@ again: FUN_2_0, FUN_1_1, FUN_0_2, - FUN_STATIC, - BCO: + FUN_STATIC: { + arity = TO_W_(StgFunInfoExtra_arity(%FUN_INFO(info))); + dofun: if (CCCS == StgHeader_ccs(untaggedfun)) { return (fun); } else { @@ -92,10 +99,8 @@ again: // attribute this allocation to the "overhead of profiling" CCS_ALLOC(BYTES_TO_WDS(SIZEOF_StgPAP), CCS_OVERHEAD); P_ pap; - W_ arity; pap = Hp - SIZEOF_StgPAP + WDS(1); SET_HDR(pap, stg_PAP_info, CCCS); - arity = TO_W_(StgFunInfoExtra_arity(%FUN_INFO(info))); StgPAP_arity(pap) = arity; StgPAP_fun(pap) = fun; StgPAP_n_args(pap) = 0; From git at git.haskell.org Sun Dec 18 01:02:06 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 01:02:06 +0000 (UTC) Subject: [commit: ghc] master: Run some tests with -fexternal-interpreter -prof (90cfa84) Message-ID: <20161218010206.B3FE53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/90cfa84981ee1f9fb756a3af1bd707674c18c034/ghc >--------------------------------------------------------------- commit 90cfa84981ee1f9fb756a3af1bd707674c18c034 Author: Simon Marlow Date: Sat Dec 17 18:08:59 2016 -0500 Run some tests with -fexternal-interpreter -prof We don't have any other tests for this, except one Template Haskell test. This would have caught the bug I just fixed in D2868, at least when validating with profiling on. Test Plan: Ran tests Reviewers: niteria, austin, erikd, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2869 GHC Trac Issues: #5654 >--------------------------------------------------------------- 90cfa84981ee1f9fb756a3af1bd707674c18c034 testsuite/config/ghc | 4 +++- testsuite/tests/profiling/should_run/all.T | 24 ++++++++++++++++++------ 2 files changed, 21 insertions(+), 7 deletions(-) diff --git a/testsuite/config/ghc b/testsuite/config/ghc index b7d9cbc..b9991d7 100644 --- a/testsuite/config/ghc +++ b/testsuite/config/ghc @@ -30,7 +30,7 @@ config.other_ways = ['prof', 'normal_h', 'llvm', 'debugllvm', 'profllvm', 'profoptllvm', 'profthreadedllvm', 'debug', - 'ghci-ext', + 'ghci-ext', 'ghci-ext-prof', 'ext-interp'] if (ghc_with_native_codegen == 1): @@ -100,6 +100,7 @@ config.way_flags = { 'profoptllvm' : ['-O', '-prof', '-static', '-fprof-auto', '-fllvm'], 'profthreadedllvm' : ['-O', '-prof', '-static', '-fprof-auto', '-threaded', '-fllvm'], 'ghci-ext' : ['--interactive', '-v0', '-ignore-dot-ghci', '-fno-ghci-history', '-fexternal-interpreter', '+RTS', '-I0.1', '-RTS'], + 'ghci-ext-prof' : ['--interactive', '-v0', '-ignore-dot-ghci', '-fno-ghci-history', '-fexternal-interpreter', '-prof', '+RTS', '-I0.1', '-RTS'], 'ext-interp' : ['-fexternal-interpreter'], } @@ -137,6 +138,7 @@ config.way_rts_flags = { 'profoptllvm' : ['-hc', '-p'], 'profthreadedllvm' : ['-p'], 'ghci-ext' : [], + 'ghci-ext-prof' : [], 'ext-interp' : [], } diff --git a/testsuite/tests/profiling/should_run/all.T b/testsuite/tests/profiling/should_run/all.T index 5faca29..875a98e 100644 --- a/testsuite/tests/profiling/should_run/all.T +++ b/testsuite/tests/profiling/should_run/all.T @@ -13,7 +13,7 @@ test('T11489', [req_profiling, extra_clean(['T11489.prof', 'T11489.hp'])], # Below this line, run tests only with profiling ways. setTestOpts(req_profiling) -setTestOpts(extra_ways(['prof'])) +setTestOpts(extra_ways(['prof', 'ghci-ext-prof'])) setTestOpts(only_ways(prof_ways)) setTestOpts(keep_prof_callstacks) @@ -21,7 +21,8 @@ extra_prof_ways = ['prof', 'prof_hc_hb', 'prof_hb', 'prof_hd', 'prof_hy', 'prof_ expect_broken_for_10037 = expect_broken_for( 10037, - [w for w in prof_ways if w not in opt_ways]) # e.g. prof and profllvm + [w for w in prof_ways if w not in opt_ways and w != 'ghci-ext-prof']) + # e.g. prof and profllvm test('heapprof001', [when(have_profiling(), extra_ways(extra_prof_ways)), extra_run_opts('7')], @@ -69,7 +70,12 @@ test('T949', [extra_ways(extra_prof_ways)], compile_and_run, ['']) # The results for 'prof' are fine, but the ordering changes. # We care more about getting the optimised results right, so ignoring # this for now. -test('ioprof', [expect_broken_for_10037, exit_code(1)], compile_and_run, +test('ioprof', + [expect_broken_for_10037, + exit_code(1), + omit_ways(['ghci-ext-prof']) # doesn't work with exit_code(1) + ], + compile_and_run, ['-fno-full-laziness -fno-state-hack']) # Note [consistent stacks] # These two examples are from the User's Guide: @@ -89,11 +95,17 @@ test('T5559', [], compile_and_run, ['']) # -fno-state-hack # -fno-full-laziness -test('callstack001', [expect_broken_for_10037], +test('callstack001', # unoptimised results are different w.r.t. CAF attribution - compile_and_run, ['-fprof-auto-calls -fno-full-laziness -fno-state-hack']) + [ expect_broken_for_10037, + omit_ways(['ghci-ext-prof']), # produces a different stack + ], compile_and_run, + ['-fprof-auto-calls -fno-full-laziness -fno-state-hack']) -test('callstack002', [], compile_and_run, +test('callstack002', + [ omit_ways(['ghci-ext-prof']), # produces a different stack + ], + compile_and_run, ['-fprof-auto-calls -fno-full-laziness -fno-state-hack']) # Should not stack overflow with -prof -fprof-auto From git at git.haskell.org Sun Dec 18 01:02:09 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 01:02:09 +0000 (UTC) Subject: [commit: ghc] master: Reexport Language.Haskell.TH.Lib from Language.Haskell.TH (343b147) Message-ID: <20161218010209.9210B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/343b1473fa3ad1f90e4f9708dbc4d8127382dc36/ghc >--------------------------------------------------------------- commit 343b1473fa3ad1f90e4f9708dbc4d8127382dc36 Author: Ryan Scott Date: Sat Dec 17 18:08:36 2016 -0500 Reexport Language.Haskell.TH.Lib from Language.Haskell.TH Reexporting `Language.Haskell.TH.Lib` from `Language.Haskell.TH` ensures that `Language.Haskell.TH` will continue to expose all of the functions that `Language.Haskell.TH.Lib` does in the future. Fixes #12992. Test Plan: ./validate Reviewers: austin, bgamari, goldfire Reviewed By: bgamari, goldfire Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2867 GHC Trac Issues: #12992 >--------------------------------------------------------------- 343b1473fa3ad1f90e4f9708dbc4d8127382dc36 libraries/template-haskell/Language/Haskell/TH.hs | 85 +---------------- .../template-haskell/Language/Haskell/TH/Lib.hs | 104 ++++++++++++++++++++- libraries/template-haskell/changelog.md | 11 +++ 3 files changed, 115 insertions(+), 85 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 343b1473fa3ad1f90e4f9708dbc4d8127382dc36 From git at git.haskell.org Sun Dec 18 01:02:12 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 01:02:12 +0000 (UTC) Subject: [commit: ghc] master: rts/win32/IOManager: Fix integer types (2d1beb1) Message-ID: <20161218010212.478993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2d1beb1ec84c2d22c6be83944ef4ea8626abd76a/ghc >--------------------------------------------------------------- commit 2d1beb1ec84c2d22c6be83944ef4ea8626abd76a Author: Ben Gamari Date: Sat Dec 17 18:08:00 2016 -0500 rts/win32/IOManager: Fix integer types This code has been broken on 64-bit systems for some time: the length and timeout arguments of `addIORequest` and `addDelayRequest`, respectively, were declared as `int`. However, they were passed Haskell integers from their respective primops. Integer overflow and madness ensued. This resulted in #7325 and who knows what else. Also, there were a few left-over `BOOL`s in here which were not passed to Windows system calls; these were changed to C99 `bool`s. However, there is still a bit of signedness inconsistency within the `delay#` call-chain, * `GHC.Conc.IO.threadDelay` and the `delay#` primop accept `Int` arguments * The `delay#` implementation in `PrimOps.cmm` expects the timeout as a `W_` * `AsyncIO.c:addDelayRequest` expects an `HsInt` (was `int` prior to this patch) * `IOManager.c:AddDelayRequest` expects an `HsInt`` (was `int`) * The Windows `Sleep` function expects a `DWORD` (which is unsigned) Test Plan: Validate on Windows Reviewers: erikd, austin, simonmar, Phyx Reviewed By: Phyx Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2861 GHC Trac Issues: #7325 >--------------------------------------------------------------- 2d1beb1ec84c2d22c6be83944ef4ea8626abd76a rts/win32/AsyncIO.c | 16 ++++++++-------- rts/win32/AsyncIO.h | 8 ++++---- rts/win32/IOManager.c | 12 ++++++------ rts/win32/IOManager.h | 18 +++++++++--------- 4 files changed, 27 insertions(+), 27 deletions(-) diff --git a/rts/win32/AsyncIO.c b/rts/win32/AsyncIO.c index 6a05f68..9e6594f 100644 --- a/rts/win32/AsyncIO.c +++ b/rts/win32/AsyncIO.c @@ -40,8 +40,8 @@ typedef struct CompletedReq { unsigned int reqID; - int len; - int errCode; + HsInt len; + HsInt errCode; } CompletedReq; #define MAX_REQUESTS 200 @@ -58,9 +58,9 @@ static int issued_reqs; static void onIOComplete(unsigned int reqID, int fd STG_UNUSED, - int len, + HsInt len, void* buf STG_UNUSED, - int errCode) + HsInt errCode) { DWORD dwRes; /* Deposit result of request in queue/table..when there's room. */ @@ -106,9 +106,9 @@ onIOComplete(unsigned int reqID, unsigned int addIORequest(int fd, - int forWriting, - int isSock, - int len, + bool forWriting, + bool isSock, + HsInt len, char* buf) { EnterCriticalSection(&queue_lock); @@ -122,7 +122,7 @@ addIORequest(int fd, } unsigned int -addDelayRequest(int usecs) +addDelayRequest(HsInt usecs) { EnterCriticalSection(&queue_lock); issued_reqs++; diff --git a/rts/win32/AsyncIO.h b/rts/win32/AsyncIO.h index bedbf5b..3737db0 100644 --- a/rts/win32/AsyncIO.h +++ b/rts/win32/AsyncIO.h @@ -10,11 +10,11 @@ extern unsigned int addIORequest(int fd, - int forWriting, - int isSock, - int len, + bool forWriting, + bool isSock, + HsInt len, char* buf); -extern unsigned int addDelayRequest(int usecs); +extern unsigned int addDelayRequest(HsInt usecs); extern unsigned int addDoProcRequest(void* proc, void* param); extern int startupAsyncIO(void); extern void shutdownAsyncIO(bool wait_threads); diff --git a/rts/win32/IOManager.c b/rts/win32/IOManager.c index f25b006..c5cae75 100644 --- a/rts/win32/IOManager.c +++ b/rts/win32/IOManager.c @@ -284,7 +284,7 @@ IOWorkerProc(PVOID param) } static -BOOL +bool NewIOWorkerThread(IOManagerState* iom) { unsigned threadId; @@ -296,7 +296,7 @@ NewIOWorkerThread(IOManagerState* iom) &threadId) ); } -BOOL +bool StartIOManager(void) { HANDLE hExit; @@ -429,9 +429,9 @@ depositWorkItem( unsigned int reqID, */ int AddIORequest ( int fd, - BOOL forWriting, - BOOL isSocket, - int len, + bool forWriting, + bool isSocket, + HsInt len, char* buffer, CompletionProc onCompletion) { @@ -461,7 +461,7 @@ AddIORequest ( int fd, * the request queue. */ BOOL -AddDelayRequest ( unsigned int usecs, +AddDelayRequest ( HsInt usecs, CompletionProc onCompletion) { WorkItem* wItem = (WorkItem*)malloc(sizeof(WorkItem)); diff --git a/rts/win32/IOManager.h b/rts/win32/IOManager.h index 94821a8..01521ca 100644 --- a/rts/win32/IOManager.h +++ b/rts/win32/IOManager.h @@ -30,9 +30,9 @@ */ typedef void (*CompletionProc)(unsigned int requestID, int fd, - int len, + HsInt len, void* buf, - int errCode); + HsInt errCode); /* * Asynchronous procedure calls executed by a worker thread @@ -44,11 +44,11 @@ typedef int (*DoProcProc)(void *param); typedef union workData { struct { int fd; - int len; + HsInt len; char *buf; } ioData; struct { - int usecs; + HsInt usecs; } delayData; struct { DoProcProc proc; @@ -80,7 +80,7 @@ extern CompletionProc onComplete; /* * Starting up and shutting down. */ -extern BOOL StartIOManager ( void ); +extern bool StartIOManager ( void ); extern void ShutdownIOManager ( bool wait_threads ); /* @@ -88,13 +88,13 @@ extern void ShutdownIOManager ( bool wait_threads ); * completion routine is supplied, which the worker thread * will invoke upon completion. */ -extern int AddDelayRequest ( unsigned int usecs, +extern int AddDelayRequest ( HsInt usecs, CompletionProc onCompletion); extern int AddIORequest ( int fd, - BOOL forWriting, - BOOL isSocket, - int len, + bool forWriting, + bool isSocket, + HsInt len, char* buffer, CompletionProc onCompletion); From git at git.haskell.org Sun Dec 18 01:02:15 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 01:02:15 +0000 (UTC) Subject: [commit: ghc] master: Improve StringBuffer and FastString docs (21dde81) Message-ID: <20161218010215.04CED3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/21dde8126d615a082648c916a3e20d9878f22517/ghc >--------------------------------------------------------------- commit 21dde8126d615a082648c916a3e20d9878f22517 Author: Phil Ruffwind Date: Sat Dec 17 18:09:06 2016 -0500 Improve StringBuffer and FastString docs This area of code contains a lot of unsafe functionality, so it might be worth documenting to reduce the risk of misuse. Test Plan: inspection Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2872 >--------------------------------------------------------------- 21dde8126d615a082648c916a3e20d9878f22517 compiler/utils/FastString.hs | 13 +++++++++++++ compiler/utils/StringBuffer.hs | 42 ++++++++++++++++++++++++++++++++++++++---- 2 files changed, 51 insertions(+), 4 deletions(-) diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs index 8f76584..8d1bbb5 100644 --- a/compiler/utils/FastString.hs +++ b/compiler/utils/FastString.hs @@ -23,6 +23,10 @@ -- * Outputing them is fast. -- * Generated by 'sLit'. -- * Turn into 'Outputable.SDoc' with 'Outputable.ptext' +-- * Requires manual memory management. +-- Improper use may lead to memory leaks or dangling pointers. +-- * It assumes Latin-1 as the encoding, therefore it cannot represent +-- arbitrary Unicode strings. -- -- Use 'LitString' unless you want the facilities of 'FastString'. module FastString @@ -560,14 +564,19 @@ hPutFS handle fs = BS.hPut handle $ fastStringToByteString fs -- ----------------------------------------------------------------------------- -- LitStrings, here for convenience only. +-- | A 'LitString' is a pointer to some null-terminated array of bytes. type LitString = Ptr Word8 --Why do we recalculate length every time it's requested? --If it's commonly needed, we should perhaps have --data LitString = LitString {-#UNPACK#-}!Addr# {-#UNPACK#-}!Int# +-- | Wrap an unboxed address into a 'LitString'. mkLitString# :: Addr# -> LitString mkLitString# a# = Ptr a# +-- | Encode a 'String' into a newly allocated 'LitString' using Latin-1 +-- encoding. The original string must not contain non-Latin-1 characters +-- (above codepoint @0xff@). {-# INLINE mkLitString #-} mkLitString :: String -> LitString mkLitString s = @@ -583,9 +592,13 @@ mkLitString s = return p ) +-- | Decode a 'LitString' back into a 'String' using Latin-1 encoding. +-- This does not free the memory associated with 'LitString'. unpackLitString :: LitString -> String unpackLitString (Ptr p) = unpackCString# p +-- | Compute the length of a 'LitString', which must necessarily be +-- null-terminated. lengthLS :: LitString -> Int lengthLS = ptrStrLength diff --git a/compiler/utils/StringBuffer.hs b/compiler/utils/StringBuffer.hs index 7da9f6c..bac752a 100644 --- a/compiler/utils/StringBuffer.hs +++ b/compiler/utils/StringBuffer.hs @@ -89,6 +89,8 @@ instance Show StringBuffer where -- ----------------------------------------------------------------------------- -- Creation / Destruction +-- | Read a file into a 'StringBuffer'. The resulting buffer is automatically +-- managed by the garbage collector. hGetStringBuffer :: FilePath -> IO StringBuffer hGetStringBuffer fname = do h <- openBinaryFile fname ReadMode @@ -161,6 +163,8 @@ appendStringBuffers sb1 sb2 calcLen sb = len sb - cur sb size = sb1_len + sb2_len +-- | Encode a 'String' into a 'StringBuffer' as UTF-8. The resulting buffer +-- is automatically managed by the garbage collector. stringToStringBuffer :: String -> StringBuffer stringToStringBuffer str = unsafePerformIO $ do @@ -175,10 +179,15 @@ stringToStringBuffer str = -- ----------------------------------------------------------------------------- -- Grab a character --- Getting our fingers dirty a little here, but this is performance-critical +-- | Return the first UTF-8 character of a nonempty 'StringBuffer' and as well +-- the remaining portion (analogous to 'Data.List.uncons'). __Warning:__ The +-- behavior is undefined if the 'StringBuffer' is empty. The result shares +-- the same buffer as the original. Similar to 'utf8DecodeChar', if the +-- character cannot be decoded as UTF-8, '\0' is returned. {-# INLINE nextChar #-} nextChar :: StringBuffer -> (Char,StringBuffer) nextChar (StringBuffer buf len (I# cur#)) = + -- Getting our fingers dirty a little here, but this is performance-critical inlinePerformIO $ do withForeignPtr buf $ \(Ptr a#) -> do case utf8DecodeChar# (a# `plusAddr#` cur#) of @@ -186,6 +195,10 @@ nextChar (StringBuffer buf len (I# cur#)) = let cur' = I# (cur# +# nBytes#) in return (C# c#, StringBuffer buf len cur') +-- | Return the first UTF-8 character of a nonempty 'StringBuffer' (analogous +-- to 'Data.List.head'). __Warning:__ The behavior is undefined if the +-- 'StringBuffer' is empty. Similar to 'utf8DecodeChar', if the character +-- cannot be decoded as UTF-8, '\0' is returned. currentChar :: StringBuffer -> Char currentChar = fst . nextChar @@ -200,29 +213,50 @@ prevChar (StringBuffer buf _ cur) _ = -- ----------------------------------------------------------------------------- -- Moving +-- | Return a 'StringBuffer' with the first UTF-8 character removed (analogous +-- to 'Data.List.tail'). __Warning:__ The behavior is undefined if the +-- 'StringBuffer' is empty. The result shares the same buffer as the +-- original. stepOn :: StringBuffer -> StringBuffer stepOn s = snd (nextChar s) -offsetBytes :: Int -> StringBuffer -> StringBuffer +-- | Return a 'StringBuffer' with the first @n@ bytes removed. __Warning:__ +-- If there aren't enough characters, the returned 'StringBuffer' will be +-- invalid and any use of it may lead to undefined behavior. The result +-- shares the same buffer as the original. +offsetBytes :: Int -- ^ @n@, the number of bytes + -> StringBuffer + -> StringBuffer offsetBytes i s = s { cur = cur s + i } +-- | Compute the difference in offset between two 'StringBuffer's that share +-- the same buffer. __Warning:__ The behavior is undefined if the +-- 'StringBuffer's use separate buffers. byteDiff :: StringBuffer -> StringBuffer -> Int byteDiff s1 s2 = cur s2 - cur s1 +-- | Check whether a 'StringBuffer' is empty (analogous to 'Data.List.null'). atEnd :: StringBuffer -> Bool atEnd (StringBuffer _ l c) = l == c -- ----------------------------------------------------------------------------- -- Conversion -lexemeToString :: StringBuffer -> Int {-bytes-} -> String +-- | Decode the first @n@ bytes of a 'StringBuffer' as UTF-8 into a 'String'. +-- Similar to 'utf8DecodeChar', if the character cannot be decoded as UTF-8, +-- they will be replaced with '\0'. +lexemeToString :: StringBuffer + -> Int -- ^ @n@, the number of bytes + -> String lexemeToString _ 0 = "" lexemeToString (StringBuffer buf _ cur) bytes = inlinePerformIO $ withForeignPtr buf $ \ptr -> utf8DecodeString (ptr `plusPtr` cur) bytes -lexemeToFastString :: StringBuffer -> Int {-bytes-} -> FastString +lexemeToFastString :: StringBuffer + -> Int -- ^ @n@, the number of bytes + -> FastString lexemeToFastString _ 0 = nilFS lexemeToFastString (StringBuffer buf _ cur) len = inlinePerformIO $ From git at git.haskell.org Sun Dec 18 01:02:17 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 01:02:17 +0000 (UTC) Subject: [commit: ghc] master: Docs: Delete duplicate paragraph in user guide (e0fe7c3) Message-ID: <20161218010217.B29083A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e0fe7c3131c4a18ddd9dd9f2afdd46cafc8cd7ae/ghc >--------------------------------------------------------------- commit e0fe7c3131c4a18ddd9dd9f2afdd46cafc8cd7ae Author: Siddhanathan Shanmugam Date: Sat Dec 17 18:09:13 2016 -0500 Docs: Delete duplicate paragraph in user guide Removes duplicate paragraph in user guide. The same paragraph is repeated below this one. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2874 >--------------------------------------------------------------- e0fe7c3131c4a18ddd9dd9f2afdd46cafc8cd7ae docs/users_guide/intro.rst | 8 -------- 1 file changed, 8 deletions(-) diff --git a/docs/users_guide/intro.rst b/docs/users_guide/intro.rst index 677f462..ad6763c 100644 --- a/docs/users_guide/intro.rst +++ b/docs/users_guide/intro.rst @@ -146,14 +146,6 @@ numbering GHC versions: branch. For example, ``6.8.1.20040225`` would be a snapshot of the ``6.8`` branch during the development of ``6.8.2``. - The value of ``__GLASGOW_HASKELL__`` for a snapshot release is the - integer ⟨xyy⟩. You should never write any conditional code which - tests for this value, however: since interfaces change on a - day-to-day basis, and we don't have finer granularity in the values - of ``__GLASGOW_HASKELL__``, you should only conditionally compile - using predicates which test whether ``__GLASGOW_HASKELL__`` is equal - to, later than, or earlier than a given major release. - We may make snapshot releases of the HEAD `available for download `__, and the latest sources are available from From git at git.haskell.org Sun Dec 18 02:32:39 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 02:32:39 +0000 (UTC) Subject: [commit: ghc] master: Allow use of the external interpreter in stage1. (52ba947) Message-ID: <20161218023239.995033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/52ba9470a7e85d025dc84a6789aa809cdd68b566/ghc >--------------------------------------------------------------- commit 52ba9470a7e85d025dc84a6789aa809cdd68b566 Author: Shea Levy Date: Sat Dec 17 20:08:58 2016 -0500 Allow use of the external interpreter in stage1. Now that we have -fexternal-interpreter, we can lose most of the GHCI ifdefs. Reviewers: simonmar, goldfire, austin, hvr, bgamari Reviewed By: simonmar Subscribers: RyanGlScott, mpickering, angerman, thomie Differential Revision: https://phabricator.haskell.org/D2826 >--------------------------------------------------------------- 52ba9470a7e85d025dc84a6789aa809cdd68b566 compiler/deSugar/Coverage.hs | 8 +-- compiler/ghc.cabal.in | 21 +++--- compiler/ghci/ByteCodeGen.hs | 4 ++ compiler/ghci/ByteCodeInstr.hs | 4 ++ compiler/ghci/ByteCodeTypes.hs | 6 +- compiler/ghci/GHCi.hs | 27 +++++++- compiler/ghci/Linker.hs | 10 +++ compiler/hsSyn/HsExpr.hs | 13 ---- compiler/main/DriverPipeline.hs | 4 -- compiler/main/DynFlags.hs | 29 -------- compiler/main/GHC.hs | 38 ++--------- compiler/main/GhcMake.hs | 8 --- compiler/main/Hooks.hs | 14 ---- compiler/main/HscMain.hs | 24 ------- compiler/main/HscTypes.hs | 28 -------- compiler/main/InteractiveEval.hs | 7 +- compiler/main/InteractiveEvalTypes.hs | 9 ++- compiler/rename/RnEnv.hs | 4 -- compiler/rename/RnSplice.hs | 22 ------ compiler/simplCore/CoreMonad.hs | 8 --- compiler/specialise/SpecConstr.hs | 19 +----- compiler/typecheck/TcAnnotations.hs | 19 ------ compiler/typecheck/TcRnDriver.hs | 23 +------ compiler/typecheck/TcRnMonad.hs | 16 ----- compiler/typecheck/TcRnTypes.hs | 8 --- compiler/typecheck/TcSplice.hs | 20 ------ compiler/typecheck/TcSplice.hs-boot | 4 -- ghc.mk | 5 +- libraries/ghci/GHCi/BreakArray.hs | 6 ++ libraries/ghci/GHCi/InfoTable.hsc | 125 ++++++++++++++++++---------------- libraries/ghci/GHCi/Message.hs | 33 ++++++++- libraries/ghci/GHCi/Run.hs | 13 ---- libraries/ghci/ghci.cabal.in | 21 ++++-- 33 files changed, 195 insertions(+), 405 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 52ba9470a7e85d025dc84a6789aa809cdd68b566 From git at git.haskell.org Sun Dec 18 03:41:04 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 03:41:04 +0000 (UTC) Subject: [commit: ghc] master: Check family instance consistency of hs-boot families later, fixes #11062. (25b70a2) Message-ID: <20161218034104.C36F83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/25b70a29f6236b591252bf5a361a1547f0ffee51/ghc >--------------------------------------------------------------- commit 25b70a29f6236b591252bf5a361a1547f0ffee51 Author: Edward Z. Yang Date: Thu Dec 15 18:05:33 2016 -0800 Check family instance consistency of hs-boot families later, fixes #11062. Summary: With hs-boot files, some type families may be defined in the module we are typechecking. In this case, we are not allowed to poke these families until after we typecheck our local declarations. So we first check everything involving non-recursive families, and then check the recursive families as we finish kind-checking them. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: goldfire, austin, simonpj, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2859 GHC Trac Issues: #11062 >--------------------------------------------------------------- 25b70a29f6236b591252bf5a361a1547f0ffee51 compiler/typecheck/FamInst.hs | 73 ++++++++++++++++++++-- compiler/typecheck/TcRnDriver.hs | 4 +- compiler/typecheck/TcRnMonad.hs | 1 + compiler/typecheck/TcRnTypes.hs | 7 +++ compiler/typecheck/TcTyClsDecls.hs | 4 ++ testsuite/driver/extra_files.py | 1 + .../A.hs => typecheck/should_compile/T11062.hs} | 4 +- .../should_compile/T11062.hs-boot} | 3 +- .../A.hs => typecheck/should_compile/T11062a.hs} | 4 +- testsuite/tests/typecheck/should_compile/all.T | 2 + 10 files changed, 89 insertions(+), 14 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 25b70a29f6236b591252bf5a361a1547f0ffee51 From git at git.haskell.org Sun Dec 18 10:55:19 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 10:55:19 +0000 (UTC) Subject: [commit: ghc] master: Fix Haddock comment typo. (630cfc3) Message-ID: <20161218105519.65C153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/630cfc382084c48c8df84a2ac59c76710ae7e0e8/ghc >--------------------------------------------------------------- commit 630cfc382084c48c8df84a2ac59c76710ae7e0e8 Author: Edward Z. Yang Date: Sun Dec 18 02:55:04 2016 -0800 Fix Haddock comment typo. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 630cfc382084c48c8df84a2ac59c76710ae7e0e8 compiler/typecheck/FamInst.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs index 747100f..0c1bdef 100644 --- a/compiler/typecheck/FamInst.hs +++ b/compiler/typecheck/FamInst.hs @@ -257,7 +257,7 @@ checkFamInstConsistency famInstMods directlyImpMods ; let (check_now, check_later) -- NB: == this_mod only holds if there's an hs-boot file; -- otherwise we cannot possible see instances for families - -- *defined by the module we are compiling* in imports. + -- defined by the module we are compiling in imports. = partition ((/= this_mod) . nameModule . fi_fam) (famInstEnvElts env1) ; mapM_ (checkForConflicts (emptyFamInstEnv, env2)) check_now From git at git.haskell.org Sun Dec 18 15:52:15 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 15:52:15 +0000 (UTC) Subject: [commit: ghc] master: Introduce unboxedSum{Data, Type}Name to template-haskell (b5d788a) Message-ID: <20161218155215.8BDA33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b5d788aa0e73fdf22cca3f88962e7652b07073cc/ghc >--------------------------------------------------------------- commit b5d788aa0e73fdf22cca3f88962e7652b07073cc Author: Ryan Scott Date: Sun Dec 18 10:41:33 2016 -0500 Introduce unboxedSum{Data,Type}Name to template-haskell Summary: In D2448 (which introduced Template Haskell support for unboxed sums), I neglected to add `unboxedSumDataName` and `unboxedSumTypeName` functions, since there wasn't any way you could write unboxed sum data or type constructors in prefix form to begin with (see #12514). But even if you can't write these `Name`s directly in source code, it would still be nice to be able to use these `Name`s in Template Haskell (for instance, to be able to treat unboxed sum type constructors like any other type constructors). Along the way, this uncovered a minor bug in `isBuiltInOcc_maybe` in `TysWiredIn`, which was calculating the arity of unboxed sum data constructors incorrectly. Test Plan: make test TEST=T12478_5 Reviewers: osa1, goldfire, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2854 GHC Trac Issues: #12478, #12514 >--------------------------------------------------------------- b5d788aa0e73fdf22cca3f88962e7652b07073cc compiler/basicTypes/Lexeme.hs | 18 ++++++++- compiler/prelude/TysWiredIn.hs | 2 +- libraries/template-haskell/Language/Haskell/TH.hs | 2 + .../template-haskell/Language/Haskell/TH/Syntax.hs | 43 ++++++++++++++++++++++ testsuite/tests/th/T12478_5.hs | 17 +++++++++ testsuite/tests/th/all.T | 1 + 6 files changed, 80 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/Lexeme.hs b/compiler/basicTypes/Lexeme.hs index 7012f5a..dadc79c 100644 --- a/compiler/basicTypes/Lexeme.hs +++ b/compiler/basicTypes/Lexeme.hs @@ -156,8 +156,10 @@ okConIdOcc :: String -> Bool okConIdOcc str = okIdOcc str || is_tuple_name1 True str || -- Is it a boxed tuple... - is_tuple_name1 False str - -- ...or an unboxed tuple (Trac #12407)? + is_tuple_name1 False str || + -- ...or an unboxed tuple (Trac #12407)... + is_sum_name1 str + -- ...or an unboxed sum (Trac #12514)? where -- check for tuple name, starting at the beginning is_tuple_name1 True ('(' : rest) = is_tuple_name2 True rest @@ -172,6 +174,18 @@ okConIdOcc str = okIdOcc str || | isSpace ws = is_tuple_name2 boxed rest is_tuple_name2 _ _ = False + -- check for sum name, starting at the beginning + is_sum_name1 ('(' : '#' : rest) = is_sum_name2 False rest + is_sum_name1 _ = False + + -- check for sum tail, only allowing at most one underscore + is_sum_name2 _ "#)" = True + is_sum_name2 underscore ('|' : rest) = is_sum_name2 underscore rest + is_sum_name2 False ('_' : rest) = is_sum_name2 True rest + is_sum_name2 underscore (ws : rest) + | isSpace ws = is_sum_name2 underscore rest + is_sum_name2 _ _ = False + -- | Is this an acceptable symbolic constructor name, assuming it -- starts with an acceptable character? okConSymOcc :: String -> Bool diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index 6e028fc..ce89e02 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -709,7 +709,7 @@ isBuiltInOcc_maybe occ = , Just rest'' <- "_" `stripPrefix` rest' , (pipes2, rest''') <- BS.span (=='|') rest'' , "#)" <- rest''' - -> let arity = BS.length pipes1 + BS.length pipes2 + -> let arity = BS.length pipes1 + BS.length pipes2 + 1 alt = BS.length pipes1 + 1 in Just $ dataConName $ sumDataCon alt arity _ -> Nothing diff --git a/libraries/template-haskell/Language/Haskell/TH.hs b/libraries/template-haskell/Language/Haskell/TH.hs index 5a49793..fd5c06f 100644 --- a/libraries/template-haskell/Language/Haskell/TH.hs +++ b/libraries/template-haskell/Language/Haskell/TH.hs @@ -60,6 +60,8 @@ module Language.Haskell.TH( -- ** Built-in names tupleTypeName, tupleDataName, -- Int -> Name unboxedTupleTypeName, unboxedTupleDataName, -- :: Int -> Name + unboxedSumTypeName, -- :: SumArity -> Name + unboxedSumDataName, -- :: SumAlt -> SumArity -> Name -- * The algebraic data types -- | The lowercase versions (/syntax operators/) of these constructors are diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index c9bccf6..9de531a 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -1199,6 +1199,49 @@ mk_unboxed_tup_name n space n_commas = n - 1 tup_mod = mkModName "GHC.Tuple" +-- Unboxed sum data and type constructors +-- | Unboxed sum data constructor +unboxedSumDataName :: SumAlt -> SumArity -> Name +-- | Unboxed sum type constructor +unboxedSumTypeName :: SumArity -> Name + +unboxedSumDataName alt arity + | alt > arity + = error $ prefix ++ "Index out of bounds." ++ debug_info + + | alt <= 0 + = error $ prefix ++ "Alt must be > 0." ++ debug_info + + | arity < 2 + = error $ prefix ++ "Arity must be >= 2." ++ debug_info + + | otherwise + = Name (mkOccName sum_occ) + (NameG DataName (mkPkgName "ghc-prim") (mkModName "GHC.Prim")) + + where + prefix = "unboxedSumDataName: " + debug_info = " (alt: " ++ show alt ++ ", arity: " ++ show arity ++ ")" + + -- Synced with the definition of mkSumDataConOcc in TysWiredIn + sum_occ = '(' : '#' : bars nbars_before ++ '_' : bars nbars_after ++ "#)" + bars i = replicate i '|' + nbars_before = alt - 1 + nbars_after = arity - alt + +unboxedSumTypeName arity + | arity < 2 + = error $ "unboxedSumTypeName: Arity must be >= 2." + ++ " (arity: " ++ show arity ++ ")" + + | otherwise + = Name (mkOccName sum_occ) + (NameG TcClsName (mkPkgName "ghc-prim") (mkModName "GHC.Prim")) + + where + -- Synced with the definition of mkSumTyConOcc in TysWiredIn + sum_occ = '(' : '#' : replicate (arity - 1) '|' ++ "#)" + ----------------------------------------------------- -- Locations ----------------------------------------------------- diff --git a/testsuite/tests/th/T12478_5.hs b/testsuite/tests/th/T12478_5.hs new file mode 100644 index 0000000..bbbcb55 --- /dev/null +++ b/testsuite/tests/th/T12478_5.hs @@ -0,0 +1,17 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE UnboxedSums #-} +module T12478_5 where + +import Language.Haskell.TH + +foo :: $(conT (unboxedSumTypeName 2) `appT` conT ''() `appT` conT ''()) + -> $(conT (unboxedSumTypeName 2) `appT` conT ''() `appT` conT ''()) +foo $(conP (unboxedSumDataName 1 2) [conP '() []]) + = $(conE (unboxedSumDataName 2 2) `appE` conE '()) +foo $(conP (unboxedSumDataName 2 2) [conP '() []]) + = $(conE (unboxedSumDataName 2 2) `appE` conE '()) + +foo2 :: (# () | () #) + -> $(conT (unboxedSumTypeName 2) `appT` conT ''() `appT` conT ''()) +foo2 (# () | #) = $(conE (unboxedSumDataName 2 2) `appE` conE '()) +foo2 $(conP (unboxedSumDataName 2 2) [conP '() []]) = (# | () #) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index ce4c5f5..66a7a9f 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -438,6 +438,7 @@ test('T12478_1', omit_ways(['ghci']), compile_and_run, test('T12478_2', omit_ways(['ghci']), compile_and_run, ['-v0']) test('T12478_3', omit_ways(['ghci']), compile, ['-v0']) test('T12478_4', omit_ways(['ghci']), compile_fail, ['-v0']) +test('T12478_5', omit_ways(['ghci']), compile, ['-v0']) test('T12513', omit_ways(['ghci']), compile_fail, ['-v0']) test('T12530', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques']) test('T12646', normal, compile, ['-v0']) From git at git.haskell.org Sun Dec 18 15:52:18 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 15:52:18 +0000 (UTC) Subject: [commit: ghc] master: Fix #12998 by removing CTimer (513eb6a) Message-ID: <20161218155218.425BF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/513eb6a0638a1c64b9d76bcab39ed80cdd9dbb27/ghc >--------------------------------------------------------------- commit 513eb6a0638a1c64b9d76bcab39ed80cdd9dbb27 Author: Ryan Scott Date: Sun Dec 18 10:41:48 2016 -0500 Fix #12998 by removing CTimer Summary: CTimer is a wrapper around `timer_t`, which is a typedef for `void*` on most platforms. The issue is that GHC's `FPTOOLS_CHECK_HTYPE` is not robust enough to discern pointer types from non-pointer types, so it mistakenly labels `timer_t` as a `Double` or `Int32` (depending on how many bits a pointer takes up on your platform). This wreaks havoc when trying to give it certain type class instances, as noted in https://phabricator.haskell.org/rGHCffc2327070dbb664bdb407a804121eacb2a7c734. For now, the simplest thing to do would be removing `CTimer`, since: 1. The original author (@DanielG) didn't have a particular use in mind for `timer_t` when he fixed #12795. 2. `CTimer` hasn't appeared in a release of `base` yet. Fixes #12998. Reviewers: austin, hvr, bgamari, DanielG, trofi Reviewed By: bgamari, trofi Subscribers: thomie, DanielG, erikd Differential Revision: https://phabricator.haskell.org/D2876 GHC Trac Issues: #12795, #12998 >--------------------------------------------------------------- 513eb6a0638a1c64b9d76bcab39ed80cdd9dbb27 libraries/base/System/Posix/Types.hs | 17 +++++++---------- libraries/base/changelog.md | 2 +- libraries/base/configure.ac | 1 - 3 files changed, 8 insertions(+), 12 deletions(-) diff --git a/libraries/base/System/Posix/Types.hs b/libraries/base/System/Posix/Types.hs index 0e9e2ae..da4fc60 100644 --- a/libraries/base/System/Posix/Types.hs +++ b/libraries/base/System/Posix/Types.hs @@ -92,9 +92,13 @@ module System.Posix.Types ( #if defined(HTYPE_KEY_T) CKey(..), #endif -#if defined(HTYPE_TIMER_T) - CTimer(..), -#endif +-- We can't support CTimer (timer_t) yet, as FPTOOLS_CHECK_HTYPE doesn't have +-- the ability to discern pointer types (like void*, which timer_t usually is) +-- from non-pointer types. See GHC Trac #12998. +-- +-- #if defined(HTYPE_TIMER_T) +-- CTimer(..), +-- #endif Fd(..), @@ -132,9 +136,6 @@ import GHC.Base import GHC.Enum import GHC.Num import GHC.Real -#if defined(HTYPE_TIMER_T) -import GHC.Float -#endif -- import GHC.Prim import GHC.Read import GHC.Show @@ -212,10 +213,6 @@ INTEGRAL_TYPE_WITH_CTYPE(CId,id_t,HTYPE_ID_T) -- | @since 4.10.0.0 INTEGRAL_TYPE_WITH_CTYPE(CKey,key_t,HTYPE_KEY_T) #endif -#if defined(HTYPE_TIMER_T) --- | @since 4.10.0.0 -FLOATING_TYPE_WITH_CTYPE(CTimer,timer_t,HTYPE_TIMER_T) -#endif -- Make an Fd type rather than using CInt everywhere INTEGRAL_TYPE(Fd,CInt) diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index d2e738b..e0cd384 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -31,7 +31,7 @@ * Added `Eq1`, `Ord1`, `Read1` and `Show1` instances for `NonEmpty`. * Add wrappers for `blksize_t`, `blkcnt_t`, `clockid_t`, `fsblkcnt_t`, - `fsfilcnt_t`, `id_t`, `key_t` and `timer_t` to System.Posix.Types (#12795) + `fsfilcnt_t`, `id_t`, and `key_t` to System.Posix.Types (#12795) * Raw buffer operations in `GHC.IO.FD` are now strict in the buffer, offset, and length operations (#9696) diff --git a/libraries/base/configure.ac b/libraries/base/configure.ac index e6c8a9b..c99c284 100644 --- a/libraries/base/configure.ac +++ b/libraries/base/configure.ac @@ -155,7 +155,6 @@ FPTOOLS_CHECK_HTYPE(fsblkcnt_t) FPTOOLS_CHECK_HTYPE(fsfilcnt_t) FPTOOLS_CHECK_HTYPE(id_t) FPTOOLS_CHECK_HTYPE(key_t) -FPTOOLS_CHECK_HTYPE(timer_t) FPTOOLS_CHECK_HTYPE(intptr_t) FPTOOLS_CHECK_HTYPE(uintptr_t) From git at git.haskell.org Sun Dec 18 17:34:57 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 17:34:57 +0000 (UTC) Subject: [commit: ghc] master: T10296a: disable on NOSMP targets (7f5be7e) Message-ID: <20161218173457.8A2123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7f5be7e9c2ab760d78905ca7f01768931982fde8/ghc >--------------------------------------------------------------- commit 7f5be7e9c2ab760d78905ca7f01768931982fde8 Author: Sergei Trofimovich Date: Sun Dec 18 17:15:37 2016 +0000 T10296a: disable on NOSMP targets Test uses +RTS -N2, requires SMP support. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 7f5be7e9c2ab760d78905ca7f01768931982fde8 testsuite/tests/rts/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index 9f2f7f0..78ce3ad 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -363,7 +363,7 @@ test('T9405', [extra_clean(['T9405.ticky']), when(msys(), expect_broken(12714))] test('T11788', when(ghc_dynamic(), skip), run_command, ['$MAKE -s --no-print-directory T11788']) -test('T10296a', [extra_clean(['T10296a.o','T10296a_c.o','T10296a'])], +test('T10296a', [ req_smp, extra_clean(['T10296a.o','T10296a_c.o','T10296a'])], run_command, ['$MAKE -s --no-print-directory T10296a']) From git at git.haskell.org Sun Dec 18 17:35:00 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 17:35:00 +0000 (UTC) Subject: [commit: ghc] master: T8209: disable on NOSMP targets (4704d65) Message-ID: <20161218173500.4E7633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4704d65d3cc69c9da3ba453e48710089ade1785b/ghc >--------------------------------------------------------------- commit 4704d65d3cc69c9da3ba453e48710089ade1785b Author: Sergei Trofimovich Date: Sun Dec 18 17:11:56 2016 +0000 T8209: disable on NOSMP targets Test calls setNumCapabilities, requires SMP support. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 4704d65d3cc69c9da3ba453e48710089ade1785b testsuite/tests/rts/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index a645ad3..9f2f7f0 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -247,7 +247,7 @@ test('linker_unload', run_command, ['$MAKE -s --no-print-directory linker_unload']) -test('T8209', [ only_ways(threaded_ways), ignore_stdout ], +test('T8209', [ req_smp, only_ways(threaded_ways), ignore_stdout ], compile_and_run, ['']) test('T8242', [ only_ways(threaded_ways), ignore_stdout ], From git at git.haskell.org Sun Dec 18 17:35:03 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 17:35:03 +0000 (UTC) Subject: [commit: ghc] master: T12035j: disable on NOSMP targets (88e8194) Message-ID: <20161218173503.2A7073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/88e819483d9820e86d14e09654a2fc58af8ee681/ghc >--------------------------------------------------------------- commit 88e819483d9820e86d14e09654a2fc58af8ee681 Author: Sergei Trofimovich Date: Sun Dec 18 17:01:11 2016 +0000 T12035j: disable on NOSMP targets Test calls setNumCapabilities, requires SMP support. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 88e819483d9820e86d14e09654a2fc58af8ee681 testsuite/tests/typecheck/should_fail/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 9f578a0..69add40 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -416,7 +416,7 @@ test('T11990a', normal, compile_fail, ['']) test('T11990b', normal, compile_fail, ['']) test('T12035', extra_clean(['T12035.hi-boot', 'T12035.o-boot', 'T12035a.hi', 'T12035a.o']), multimod_compile_fail, ['T12035', '-v0']) -test('T12035j', extra_clean(['T12035.hi-boot', 'T12035.o-boot', 'T12035a.hi', 'T12035a.o']), +test('T12035j', [ req_smp, extra_clean(['T12035.hi-boot', 'T12035.o-boot', 'T12035a.hi', 'T12035a.o']) ], multimod_compile_fail, ['T12035', '-j2 -v0']) test('T12063', [ expect_broken(12063), extra_clean(['T12063.hi-boot', 'T12063.o-boot', 'T12063a.hi', 'T12063a.o']) ], multimod_compile_fail, ['T12063', '-v0']) From git at git.haskell.org Sun Dec 18 17:35:05 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 17:35:05 +0000 (UTC) Subject: [commit: ghc] master: regalloc_unit_tests: disable on UNREG targets (d327ebd) Message-ID: <20161218173505.E14FD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d327ebd61d844897d6f189b7799373fa16b3bc71/ghc >--------------------------------------------------------------- commit d327ebd61d844897d6f189b7799373fa16b3bc71 Author: Sergei Trofimovich Date: Sun Dec 18 17:24:13 2016 +0000 regalloc_unit_tests: disable on UNREG targets Test requires register allocator to be present (native code generator). Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- d327ebd61d844897d6f189b7799373fa16b3bc71 testsuite/tests/regalloc/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/regalloc/all.T b/testsuite/tests/regalloc/all.T index c0c01ff..99eeb1c 100644 --- a/testsuite/tests/regalloc/all.T +++ b/testsuite/tests/regalloc/all.T @@ -1,4 +1,5 @@ test('regalloc_unit_tests', - [ extra_files(['no_spills.cmm']), [ignore_stderr, only_ways(['normal'])], extra_run_opts('"' + config.libdir + '"') ], + [ when(unregisterised(), skip), extra_files(['no_spills.cmm']), + [ignore_stderr, only_ways(['normal'])], extra_run_opts('"' + config.libdir + '"') ], compile_and_run, ['-package ghc']) From git at git.haskell.org Sun Dec 18 17:35:08 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 17:35:08 +0000 (UTC) Subject: [commit: ghc] master: T8242: disable on NOSMP targets (bb74bc7) Message-ID: <20161218173508.AEC5A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bb74bc79daf8b91b21a1b68b0a406828d188ed92/ghc >--------------------------------------------------------------- commit bb74bc79daf8b91b21a1b68b0a406828d188ed92 Author: Sergei Trofimovich Date: Sun Dec 18 17:30:10 2016 +0000 T8242: disable on NOSMP targets Test calls setNumCapabilities, requires SMP support. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- bb74bc79daf8b91b21a1b68b0a406828d188ed92 testsuite/tests/rts/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index 78ce3ad..a3b16f0 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -250,7 +250,7 @@ test('linker_unload', test('T8209', [ req_smp, only_ways(threaded_ways), ignore_stdout ], compile_and_run, ['']) -test('T8242', [ only_ways(threaded_ways), ignore_stdout ], +test('T8242', [ req_smp, only_ways(threaded_ways), ignore_stdout ], compile_and_run, ['']) test('T8124', [ only_ways(threaded_ways), omit_ways(['ghci']), From git at git.haskell.org Sun Dec 18 21:26:38 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 21:26:38 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Give concrete example for #12784 in 8.0.2 release notes (dae7690) Message-ID: <20161218212638.F02BD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/dae769049f67fdc3aff92cb828206d4c68faa2cf/ghc >--------------------------------------------------------------- commit dae769049f67fdc3aff92cb828206d4c68faa2cf Author: Ryan Scott Date: Tue Dec 6 09:03:41 2016 -0500 Give concrete example for #12784 in 8.0.2 release notes Summary: We mentioned that there were "some programs" that failed to typecheck due to #12784, but given how surprisingly common this issue has been, it'd be prudent to at least give one example of the bug in the release notes. Reviewers: simonpj, bgamari, austin, rwbarton Reviewed By: rwbarton Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2786 GHC Trac Issues: #12784 (cherry picked from commit eec02ab7c8433465cc8d6be0a8889e7c6a222fb0) >--------------------------------------------------------------- dae769049f67fdc3aff92cb828206d4c68faa2cf docs/users_guide/8.0.2-notes.rst | 21 +++++++++++++++++++-- 1 file changed, 19 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/8.0.2-notes.rst b/docs/users_guide/8.0.2-notes.rst index fa7aa8d..237c3b9 100644 --- a/docs/users_guide/8.0.2-notes.rst +++ b/docs/users_guide/8.0.2-notes.rst @@ -68,8 +68,25 @@ Language foo :: m () - Some programs using :ghc-flag:`-XDefaultSignatures` that incorrectly - type-checked in GHC 8.0.1 are now rejected by GHC 8.0.2. See - :ghc-ticket:`12784` for details. + type-checked in GHC 8.0.1 are now rejected by GHC 8.0.2. Here is a + characteristic example: :: + + class Monad m => MonadSupply m where + fresh :: m Integer + default fresh :: (MonadTrans t, MonadSupply m) => t m Integer + fresh = lift fresh + + instance MonadSupply m => MonadSupply (IdentityT m) + + Note that the ``m`` in the default type signature is being used in + a completely different way than the ``m`` in the non-default signature! + We can fix this (in a backwards-compatible way) like so: :: + + class Monad m => MonadSupply m where + fresh :: m Integer + default fresh :: (MonadTrans t, MonadSupply m', m ~ t m') => m Integer + -- Same 'm Integer' after the '=>' + fresh = lift fresh - Some programs which combine default type class method implementations and overlapping instances may now fail to type-check. Here is an example: :: From git at git.haskell.org Sun Dec 18 21:26:41 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 21:26:41 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: mk/config.mk.in: enable SMP on ARMv7+ (Trac #12981) (7b4ab5b) Message-ID: <20161218212641.ADF303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/7b4ab5bde04c2cd49681068c290a3a19111ea401/ghc >--------------------------------------------------------------- commit 7b4ab5bde04c2cd49681068c290a3a19111ea401 Author: Sergei Trofimovich Date: Thu Dec 15 09:02:50 2016 +0000 mk/config.mk.in: enable SMP on ARMv7+ (Trac #12981) Before the change result of expression ArchSupportsSMP="$(if $(filter $(ARM_ISA),ARMv5 ARMv6),NO,YES)" to evaluate to ArchSupportsSMP="YES" After the change it's ArchSupportsSMP=YES Thanks to orion for the fix! Fixes Trac #12981 Signed-off-by: Sergei Trofimovich (cherry picked from commit 52c5e55348170f27f5ef1cb010c4c96ab4aa47cc) >--------------------------------------------------------------- 7b4ab5bde04c2cd49681068c290a3a19111ea401 mk/config.mk.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index 9de3537..bfaaa66 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -187,7 +187,7 @@ HaveLibDL = @HaveLibDL@ # includes/stg/SMP.h ifeq "$(TargetArch_CPP)" "arm" # We don't support load/store barriers pre-ARMv7. See #10433. -ArchSupportsSMP="$(if $(filter $(ARM_ISA),ARMv5 ARMv6),NO,YES)" +ArchSupportsSMP=$(if $(filter $(ARM_ISA),ARMv5 ARMv6),NO,YES) else ArchSupportsSMP=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 sparc powerpc powerpc64 powerpc64le aarch64))) endif From git at git.haskell.org Sun Dec 18 21:26:44 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 21:26:44 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: testsuite: Add test for #12993 (1181bb5) Message-ID: <20161218212644.C1CF53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/1181bb580ad01d56fb1b624dc6787cafb553293e/ghc >--------------------------------------------------------------- commit 1181bb580ad01d56fb1b624dc6787cafb553293e Author: Ben Gamari Date: Fri Dec 16 16:47:45 2016 -0500 testsuite: Add test for #12993 (cherry picked from commit 54706738cd452717c7ec1a91927c3941c8037c7b) >--------------------------------------------------------------- 1181bb580ad01d56fb1b624dc6787cafb553293e testsuite/tests/th/T12993.hs | 4 ++++ testsuite/tests/th/T12993_Lib.hs | 4 ++++ testsuite/tests/th/all.T | 1 + 3 files changed, 9 insertions(+) diff --git a/testsuite/tests/th/T12993.hs b/testsuite/tests/th/T12993.hs new file mode 100644 index 0000000..6082669 --- /dev/null +++ b/testsuite/tests/th/T12993.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE TemplateHaskell #-} +module T12993 where +import T12993_Lib +f = $(q) diff --git a/testsuite/tests/th/T12993_Lib.hs b/testsuite/tests/th/T12993_Lib.hs new file mode 100644 index 0000000..441b783 --- /dev/null +++ b/testsuite/tests/th/T12993_Lib.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE TemplateHaskell #-} +module T12993_Lib (q) where +data X = X { x :: Int } +q = [|x|] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 773b360..0e24b48 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -421,3 +421,4 @@ test('T12411', normal, compile_fail, ['']) test('T12788', extra_clean(['T12788_Lib.hi', 'T12788_Lib.o']), multimod_compile_fail, ['T12788.hs', '-v0 ' + config.ghc_th_way_flags]) +test('T12993', normal, multimod_compile, ['T12993.hs', '-v0']) From git at git.haskell.org Sun Dec 18 21:26:47 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 21:26:47 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Ensure flags destined for ld are properly passed (d3c18b2) Message-ID: <20161218212647.80C443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/d3c18b26e91f835794e4dbc3f5a073f15bca1a74/ghc >--------------------------------------------------------------- commit d3c18b26e91f835794e4dbc3f5a073f15bca1a74 Author: Ben Gamari Date: Thu Dec 1 11:28:47 2016 -0500 Ensure flags destined for ld are properly passed GHC uses gcc, not ld, for linking. Consequently all flags to be interpreted by ld need to be prefixed by -optl,-Wl on the GHC command line. Test Plan: Validate on OpenBSD Reviewers: austin, rwbarton Reviewed By: rwbarton Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2776 (cherry picked from commit f48f5a9ebf384e1e157b7b413e1d779f4289ddd2) >--------------------------------------------------------------- d3c18b26e91f835794e4dbc3f5a073f15bca1a74 rules/distdir-way-opts.mk | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rules/distdir-way-opts.mk b/rules/distdir-way-opts.mk index 4ebbc0e..4f943a1 100644 --- a/rules/distdir-way-opts.mk +++ b/rules/distdir-way-opts.mk @@ -200,7 +200,7 @@ $1_$2_$3_ALL_LD_OPTS = \ # Options for passing to GHC when we use it for linking $1_$2_$3_GHC_LD_OPTS = \ - $$(addprefix -optl, $$($1_$2_$3_ALL_LD_OPTS)) \ + $$(addprefix -optl-Wl, $$($1_$2_$3_ALL_LD_OPTS)) \ $$($1_$2_$3_MOST_HC_OPTS) $1_$2_$3_ALL_AS_OPTS = \ From git at git.haskell.org Sun Dec 18 21:26:50 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Dec 2016 21:26:50 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Revert "Do not init record accessors as exported" (de122b0) Message-ID: <20161218212650.364713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/de122b0162ea0b8c145b9d6ebb1543c964d2c80c/ghc >--------------------------------------------------------------- commit de122b0162ea0b8c145b9d6ebb1543c964d2c80c Author: Ben Gamari Date: Sat Dec 17 11:52:59 2016 -0500 Revert "Do not init record accessors as exported" This reverts commit 9d9eaeca03e138e0b35351c9401c832996398641 due to #12993. >--------------------------------------------------------------- de122b0162ea0b8c145b9d6ebb1543c964d2c80c compiler/basicTypes/Id.hs | 7 ------- compiler/deSugar/Desugar.hs | 5 +---- compiler/typecheck/TcTyDecls.hs | 7 +------ 3 files changed, 2 insertions(+), 17 deletions(-) diff --git a/compiler/basicTypes/Id.hs b/compiler/basicTypes/Id.hs index 990a192..e55259b 100644 --- a/compiler/basicTypes/Id.hs +++ b/compiler/basicTypes/Id.hs @@ -33,7 +33,6 @@ module Id ( mkLocalId, mkLocalCoVar, mkLocalIdOrCoVar, mkLocalIdOrCoVarWithInfo, mkLocalIdWithInfo, mkExportedLocalId, mkExportedVanillaId, - mkNonExportedLocalId, mkSysLocal, mkSysLocalM, mkSysLocalOrCoVar, mkSysLocalOrCoVarM, mkUserLocal, mkUserLocalOrCoVar, mkTemplateLocals, mkTemplateLocalsNum, mkTemplateLocal, @@ -288,12 +287,6 @@ mkExportedLocalId :: IdDetails -> Name -> Type -> Id mkExportedLocalId details name ty = Var.mkExportedLocalVar details name ty vanillaIdInfo -- Note [Free type variables] --- | Create a local 'Id' that is marked as not-exported. --- These may be removed as dead code. -mkNonExportedLocalId :: IdDetails -> Name -> Type -> Id -mkNonExportedLocalId details name ty = - Var.mkLocalVar details name ty vanillaIdInfo - mkExportedVanillaId :: Name -> Type -> Id mkExportedVanillaId name ty = Var.mkExportedLocalVar VanillaId name ty vanillaIdInfo -- Note [Free type variables] diff --git a/compiler/deSugar/Desugar.hs b/compiler/deSugar/Desugar.hs index 365e7c9..db4c867 100644 --- a/compiler/deSugar/Desugar.hs +++ b/compiler/deSugar/Desugar.hs @@ -295,10 +295,7 @@ deSugar hsc_env (text "Desugar"<+>brackets (ppr mod)) (const ()) $ do { -- Desugar the program - ; let export_set = - -- Used to be 'availsToNameSet', but we now export selectors - -- only when necessary. See #12125. - availsToNameSetWithSelectors exports + ; let export_set = availsToNameSet exports target = hscTarget dflags hpcInfo = emptyHpcInfo other_hpc_info diff --git a/compiler/typecheck/TcTyDecls.hs b/compiler/typecheck/TcTyDecls.hs index 4623744..233857c 100644 --- a/compiler/typecheck/TcTyDecls.hs +++ b/compiler/typecheck/TcTyDecls.hs @@ -949,12 +949,7 @@ mkOneRecordSelector all_cons idDetails fl lbl = flLabel fl sel_name = flSelector fl - sel_id = - -- Do not mark record selectors as exported to avoid keeping these Ids - -- alive unnecessarily. See #12125. Selectors are now marked as exported - -- when necessary by desugarer ('Desugar.addExportFlagsAndRules', also see - -- uses of 'availsToNameSetWithSelectors' in 'Desugar.hs'). - mkNonExportedLocalId rec_details sel_name sel_ty + sel_id = mkExportedLocalId rec_details sel_name sel_ty rec_details = RecSelId { sel_tycon = idDetails, sel_naughty = is_naughty } -- Find a representative constructor, con1 From git at git.haskell.org Mon Dec 19 17:28:47 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Dec 2016 17:28:47 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: fix OpenBSD linkage (wxneeded) (c5f375c) Message-ID: <20161219172847.241AA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/c5f375c53671130c79713800b13a1da53d070b84/ghc >--------------------------------------------------------------- commit c5f375c53671130c79713800b13a1da53d070b84 Author: Sergei Trofimovich Date: Sat Dec 17 20:25:19 2016 +0000 fix OpenBSD linkage (wxneeded) There is two types of options passed directly to 'ld' (and not to 'gcc' driver): - CONF_LD_LINKER_OPTS_STAGE$4 - EXTRA_LD_OPTS This changedoes two things: - split 'EXTRA_LD_OPTS' into two variables: - EXTRA_LD_OPTS (accepts 'gcc' wrapper options) - EXTRA_LD_LINKER_OPTS (accepts raw 'ld' options) - wraps all LD_LINKER options as '-Wl,' when passed to 'gcc' driver. Fixes https://phabricator.haskell.org/D2776 Signed-off-by: Sergei Trofimovich (cherry picked from commit 87c3b1d4395c3d4fc7a5272717c48f3f525da959) >--------------------------------------------------------------- c5f375c53671130c79713800b13a1da53d070b84 aclocal.m4 | 2 +- rules/build-package-way.mk | 2 +- rules/distdir-way-opts.mk | 5 +++-- 3 files changed, 5 insertions(+), 4 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 04bcf54..7723743 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -606,7 +606,7 @@ AC_DEFUN([FPTOOLS_SET_C_LD_FLAGS], x86_64-*-openbsd*) # We need -z wxneeded at least to link ghc-stage2 to workaround # W^X issue in GHCi on OpenBSD current (as of Aug 2016) - $3="$$3 -Wl,-zwxneeded" + $3="$$3 -Wl,-z,wxneeded" $4="$$4 -z wxneeded" ;; diff --git a/rules/build-package-way.mk b/rules/build-package-way.mk index 905b7f0..8f61a35 100644 --- a/rules/build-package-way.mk +++ b/rules/build-package-way.mk @@ -155,7 +155,7 @@ BINDIST_LIBS += $$($1_$2_GHCI_LIB) endif endif $$($1_$2_GHCI_LIB) : $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS) $$($1_$2_LD_SCRIPT) - $$(call cmd,LD) $$(CONF_LD_LINKER_OPTS_STAGE$4) -r $$(if $$($1_$2_LD_SCRIPT),-T $$($1_$2_LD_SCRIPT)) -o $$@ $$(EXTRA_LD_OPTS) $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS) + $$(call cmd,LD) $$(CONF_LD_LINKER_OPTS_STAGE$4) -r $$(if $$($1_$2_LD_SCRIPT),-T $$($1_$2_LD_SCRIPT)) -o $$@ $$(EXTRA_LD_LINKER_OPTS) $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS) ifeq "$$($1_$2_BUILD_GHCI_LIB)" "YES" # Don't bother making ghci libs for bootstrapping packages diff --git a/rules/distdir-way-opts.mk b/rules/distdir-way-opts.mk index 4f943a1..61e03ee 100644 --- a/rules/distdir-way-opts.mk +++ b/rules/distdir-way-opts.mk @@ -189,14 +189,15 @@ $1_$2_$3_GHC_CC_OPTS = \ $$(addprefix -optc, $$($1_$2_$3_ALL_CC_OPTS)) \ $$($1_$2_$3_MOST_HC_OPTS) -# Options for passing to plain ld +# Options for passing to gcc for linking $1_$2_$3_ALL_LD_OPTS = \ $$(WAY_$3_LD_OPTS) \ $$($1_$2_DIST_LD_OPTS) \ $$($1_$2_$3_LD_OPTS) \ $$($1_$2_EXTRA_LD_OPTS) \ $$(EXTRA_LD_OPTS) \ - $$(CONF_LD_LINKER_OPTS_STAGE$4) + $$(foreach o,$$(EXTRA_LD_LINKER_OPTS),-optl-Wl$$(comma)$$o) \ + $$(foreach o,$$(CONF_LD_LINKER_OPTS_STAGE$4),-optl-Wl$$(comma)$$o) # Options for passing to GHC when we use it for linking $1_$2_$3_GHC_LD_OPTS = \ From git at git.haskell.org Mon Dec 19 20:09:25 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Dec 2016 20:09:25 +0000 (UTC) Subject: [commit: ghc] master: Revert "Allow use of the external interpreter in stage1." (f1dfce1) Message-ID: <20161219200925.5F7633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f1dfce1cb2a823696d6d3a9ea41c2bc73d949f12/ghc >--------------------------------------------------------------- commit f1dfce1cb2a823696d6d3a9ea41c2bc73d949f12 Author: Tamar Christina Date: Mon Dec 19 19:09:18 2016 +0000 Revert "Allow use of the external interpreter in stage1." This reverts commit 52ba9470a7e85d025dc84a6789aa809cdd68b566. >--------------------------------------------------------------- f1dfce1cb2a823696d6d3a9ea41c2bc73d949f12 compiler/deSugar/Coverage.hs | 8 ++- compiler/ghc.cabal.in | 21 +++--- compiler/ghci/ByteCodeGen.hs | 4 -- compiler/ghci/ByteCodeInstr.hs | 4 -- compiler/ghci/ByteCodeTypes.hs | 6 +- compiler/ghci/GHCi.hs | 27 +------- compiler/ghci/Linker.hs | 10 --- compiler/hsSyn/HsExpr.hs | 13 ++++ compiler/main/DriverPipeline.hs | 4 ++ compiler/main/DynFlags.hs | 29 ++++++++ compiler/main/GHC.hs | 38 +++++++++-- compiler/main/GhcMake.hs | 8 +++ compiler/main/Hooks.hs | 14 ++++ compiler/main/HscMain.hs | 24 +++++++ compiler/main/HscTypes.hs | 28 ++++++++ compiler/main/InteractiveEval.hs | 7 +- compiler/main/InteractiveEvalTypes.hs | 9 +-- compiler/rename/RnEnv.hs | 4 ++ compiler/rename/RnSplice.hs | 22 ++++++ compiler/simplCore/CoreMonad.hs | 8 +++ compiler/specialise/SpecConstr.hs | 19 +++++- compiler/typecheck/TcAnnotations.hs | 19 ++++++ compiler/typecheck/TcRnDriver.hs | 23 ++++++- compiler/typecheck/TcRnMonad.hs | 16 +++++ compiler/typecheck/TcRnTypes.hs | 8 +++ compiler/typecheck/TcSplice.hs | 20 ++++++ compiler/typecheck/TcSplice.hs-boot | 4 ++ ghc.mk | 5 +- libraries/ghci/GHCi/BreakArray.hs | 6 -- libraries/ghci/GHCi/InfoTable.hsc | 125 ++++++++++++++++------------------ libraries/ghci/GHCi/Message.hs | 33 +-------- libraries/ghci/GHCi/Run.hs | 13 ++++ libraries/ghci/ghci.cabal.in | 21 ++---- 33 files changed, 405 insertions(+), 195 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f1dfce1cb2a823696d6d3a9ea41c2bc73d949f12 From git at git.haskell.org Mon Dec 19 23:19:12 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Dec 2016 23:19:12 +0000 (UTC) Subject: [commit: ghc] master: Fix timeout's timeout on Windows (6263e10) Message-ID: <20161219231912.71BB63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6263e1079a2d203fbd2e668ca99c0e901fcd1548/ghc >--------------------------------------------------------------- commit 6263e1079a2d203fbd2e668ca99c0e901fcd1548 Author: Tamar Christina Date: Mon Dec 19 00:18:57 2016 +0000 Fix timeout's timeout on Windows Summary: Timeout has been broken by my previous patch. The timeout event was not being processed correctly, as such hanging processes would not be killed as they should have been. This corrects it. Test Plan: ./validate ~/ghc/testsuite/timeout/install-inplace/bin/timeout.exe 10 "sleep 10000s" Reviewers: austin, RyanGlScott, bgamari Reviewed By: bgamari Subscribers: thomie, #ghc_windows_task_force Differential Revision: https://phabricator.haskell.org/D2880 GHC Trac Issues: #13004 >--------------------------------------------------------------- 6263e1079a2d203fbd2e668ca99c0e901fcd1548 testsuite/timeout/WinCBindings.hsc | 33 ++++++++++++++++++--------------- 1 file changed, 18 insertions(+), 15 deletions(-) diff --git a/testsuite/timeout/WinCBindings.hsc b/testsuite/timeout/WinCBindings.hsc index d9c08ee..36ba01e 100644 --- a/testsuite/timeout/WinCBindings.hsc +++ b/testsuite/timeout/WinCBindings.hsc @@ -369,21 +369,24 @@ waitForJobCompletion hJob ioPort timeout loop = do res <- getQueuedCompletionStatus ioPort p_CompletionCode p_CompletionKey p_Overlapped timeout - completionCode <- peek p_CompletionCode - - if completionCode == cJOB_OBJECT_MSG_ACTIVE_PROCESS_ZERO - then return () - else if completionCode == cJOB_OBJECT_MSG_EXIT_PROCESS - then loop - else if completionCode == cJOB_OBJECT_MSG_NEW_PROCESS - then loop - else loop - - loop - - overlapped <- peek p_Overlapped - completionKey <- peek $ castPtr p_CompletionKey - return $ if overlapped == nullPtr && completionKey /= hJob + case res of + False -> return () + True -> do + completionCode <- peek p_CompletionCode + if completionCode == cJOB_OBJECT_MSG_ACTIVE_PROCESS_ZERO + then return () + else if completionCode == cJOB_OBJECT_MSG_EXIT_PROCESS + then loop -- Debug point, do nothing for now + else if completionCode == cJOB_OBJECT_MSG_NEW_PROCESS + then loop -- Debug point, do nothing for now + else loop + + loop -- Kick it all off + + overlapped <- peek p_Overlapped + code <- peek $ p_CompletionCode + + return $ if overlapped == nullPtr && code /= cJOB_OBJECT_MSG_ACTIVE_PROCESS_ZERO then False -- Timeout occurred. *dark voice* YOU HAVE FAILED THIS TEST!. else True #endif From git at git.haskell.org Mon Dec 19 23:46:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Dec 2016 23:46:34 +0000 (UTC) Subject: [commit: ghc] master: Mark T8089 as unbroken since #7325 is now resolved (c0c1f80) Message-ID: <20161219234634.C5A6E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c0c1f801f4ca26f1db68ac527341a1cf051cb7d6/ghc >--------------------------------------------------------------- commit c0c1f801f4ca26f1db68ac527341a1cf051cb7d6 Author: Ben Gamari Date: Mon Dec 19 18:45:08 2016 -0500 Mark T8089 as unbroken since #7325 is now resolved >--------------------------------------------------------------- c0c1f801f4ca26f1db68ac527341a1cf051cb7d6 libraries/base/tests/all.T | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T index a9aee1e..6899e40 100644 --- a/libraries/base/tests/all.T +++ b/libraries/base/tests/all.T @@ -190,9 +190,7 @@ test('T9681', normal, compile_fail, ['']) # make an educated guess how long it needs to be guaranteed to reach the C # call." test('T8089', - [exit_code(99), run_timeout_multiplier(0.01), - when(opsys('mingw32'), - expect_broken_for(7325, ['normal', 'hpc', 'optasm', 'profasm']))], + [exit_code(99), run_timeout_multiplier(0.01)], compile_and_run, ['']) test('T9826',normal, compile_and_run,['']) test('T9848', From git at git.haskell.org Tue Dec 20 01:26:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Dec 2016 01:26:01 +0000 (UTC) Subject: [commit: ghc] master: Allow use of the external interpreter in stage1. (27f7925) Message-ID: <20161220012601.559E53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/27f79255634d9789f367273504545c1ebfad90a0/ghc >--------------------------------------------------------------- commit 27f79255634d9789f367273504545c1ebfad90a0 Author: Shea Levy Date: Tue Dec 20 01:19:18 2016 +0000 Allow use of the external interpreter in stage1. Summary: Now that we have -fexternal-interpreter, we can lose most of the GHCI ifdefs. This was originally added in https://phabricator.haskell.org/D2826 but that led to a compatibility issue with ghc 7.10.x on Windows. That's fixed here and the revert reverted. Reviewers: goldfire, hvr, austin, bgamari, Phyx Reviewed By: Phyx Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2884 GHC Trac Issues: #13008 >--------------------------------------------------------------- 27f79255634d9789f367273504545c1ebfad90a0 compiler/deSugar/Coverage.hs | 8 +-- compiler/ghc.cabal.in | 21 +++--- compiler/ghci/ByteCodeGen.hs | 4 ++ compiler/ghci/ByteCodeInstr.hs | 4 ++ compiler/ghci/ByteCodeTypes.hs | 6 +- compiler/ghci/{GHCi.hs => GHCi.hsc} | 50 +++++++++++++- compiler/ghci/Linker.hs | 10 +++ compiler/hsSyn/HsExpr.hs | 13 ---- compiler/main/DriverPipeline.hs | 4 -- compiler/main/DynFlags.hs | 29 -------- compiler/main/GHC.hs | 38 ++--------- compiler/main/GhcMake.hs | 8 --- compiler/main/Hooks.hs | 14 ---- compiler/main/HscMain.hs | 24 ------- compiler/main/HscTypes.hs | 28 -------- compiler/main/InteractiveEval.hs | 7 +- compiler/main/InteractiveEvalTypes.hs | 9 ++- compiler/rename/RnEnv.hs | 4 -- compiler/rename/RnSplice.hs | 22 ------ compiler/simplCore/CoreMonad.hs | 8 --- compiler/specialise/SpecConstr.hs | 19 +----- compiler/typecheck/TcAnnotations.hs | 19 ------ compiler/typecheck/TcRnDriver.hs | 23 +------ compiler/typecheck/TcRnMonad.hs | 16 ----- compiler/typecheck/TcRnTypes.hs | 8 --- compiler/typecheck/TcSplice.hs | 20 ------ compiler/typecheck/TcSplice.hs-boot | 4 -- ghc.mk | 5 +- libraries/ghci/GHCi/BreakArray.hs | 6 ++ libraries/ghci/GHCi/InfoTable.hsc | 125 ++++++++++++++++++---------------- libraries/ghci/GHCi/Message.hs | 33 ++++++++- libraries/ghci/GHCi/Run.hs | 13 ---- libraries/ghci/ghci.cabal.in | 21 ++++-- 33 files changed, 218 insertions(+), 405 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 27f79255634d9789f367273504545c1ebfad90a0 From git at git.haskell.org Tue Dec 20 07:24:42 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Dec 2016 07:24:42 +0000 (UTC) Subject: [commit: packages/hpc] master: Relax time bound on hpc. (9267329) Message-ID: <20161220072442.E8B0E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : master Link : http://git.haskell.org/packages/hpc.git/commitdiff/92673292ab7ce7878e982d0a02df3e548ef15b52 >--------------------------------------------------------------- commit 92673292ab7ce7878e982d0a02df3e548ef15b52 Author: Edward Z. Yang Date: Mon Dec 19 23:22:46 2016 -0800 Relax time bound on hpc. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 92673292ab7ce7878e982d0a02df3e548ef15b52 hpc.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hpc.cabal b/hpc.cabal index 994ca28..09e5c01 100644 --- a/hpc.cabal +++ b/hpc.cabal @@ -39,5 +39,5 @@ Library containers >= 0.4.1 && < 0.6, directory >= 1.1 && < 1.4, filepath >= 1 && < 1.5, - time >= 1.2 && < 1.7 + time >= 1.2 && < 1.8 ghc-options: -Wall From git at git.haskell.org Tue Dec 20 07:39:14 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Dec 2016 07:39:14 +0000 (UTC) Subject: [commit: ghc] wip/T9291: Add a CSE pass to Stg (#9291) (d8a45b9) Message-ID: <20161220073914.3FE673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9291 Link : http://ghc.haskell.org/trac/ghc/changeset/d8a45b9a2f716f36e2c568b86bf8c0717d3dd7ca/ghc >--------------------------------------------------------------- commit d8a45b9a2f716f36e2c568b86bf8c0717d3dd7ca Author: Joachim Breitner Date: Thu Dec 15 10:57:43 2016 -0800 Add a CSE pass to Stg (#9291) This CSE pass only targets data constructor applications. This is probably the best we can do, as function calls and primitive operations might have side-effects. Introduces the flag -fstg-cse, enabled by default with -O. Differential Revision: https://phabricator.haskell.org/D2871 >--------------------------------------------------------------- d8a45b9a2f716f36e2c568b86bf8c0717d3dd7ca compiler/coreSyn/TrieMap.hs | 6 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 3 + compiler/simplStg/SimplStg.hs | 30 +- compiler/simplStg/StgCse.hs | 357 +++++++++++++++++++++ docs/users_guide/using-optimisation.rst | 8 + testsuite/tests/{ado => simplStg}/Makefile | 0 .../should_run}/Makefile | 0 testsuite/tests/simplStg/should_run/T9291.hs | 27 ++ .../should_run/T9291.stdout} | 1 - testsuite/tests/simplStg/should_run/all.T | 12 + 11 files changed, 429 insertions(+), 16 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d8a45b9a2f716f36e2c568b86bf8c0717d3dd7ca From git at git.haskell.org Tue Dec 20 10:35:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Dec 2016 10:35:34 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #12996 (4535fa2) Message-ID: <20161220103534.371643A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4535fa2646fb0df753165ecbad25be53318ec123/ghc >--------------------------------------------------------------- commit 4535fa2646fb0df753165ecbad25be53318ec123 Author: Simon Peyton Jones Date: Tue Dec 20 00:08:42 2016 +0000 Test Trac #12996 >--------------------------------------------------------------- 4535fa2646fb0df753165ecbad25be53318ec123 testsuite/tests/perf/should_run/T12996.hs | 29 +++++++++++++++++++++++++++ testsuite/tests/perf/should_run/T12996.stdout | 24 ++++++++++++++++++++++ testsuite/tests/perf/should_run/all.T | 7 +++++++ 3 files changed, 60 insertions(+) diff --git a/testsuite/tests/perf/should_run/T12996.hs b/testsuite/tests/perf/should_run/T12996.hs new file mode 100644 index 0000000..78e6264 --- /dev/null +++ b/testsuite/tests/perf/should_run/T12996.hs @@ -0,0 +1,29 @@ +{-# OPTIONS_GHC -fno-full-laziness #-} + +module Main where + +import Control.Monad (unless) +import Data.Time.Clock +import System.IO + +data AppState = AppState [Int] + +cycleState :: [Int] -> [Int] +cycleState w = filter (check w) w + +check :: [Int] -> Int -> Bool +check world pos = pos `elem` world + +initialSet :: [Int] +initialSet = [1] + +main :: IO () +main = appLoop 24 (AppState initialSet) + +appLoop :: Int -> AppState -> IO () +appLoop n s + | n == 0 = return () + | otherwise = do let AppState state = s + print state + appLoop (n-1) $ AppState (cycleState state) + diff --git a/testsuite/tests/perf/should_run/T12996.stdout b/testsuite/tests/perf/should_run/T12996.stdout new file mode 100644 index 0000000..a0fb885 --- /dev/null +++ b/testsuite/tests/perf/should_run/T12996.stdout @@ -0,0 +1,24 @@ +[1] +[1] +[1] +[1] +[1] +[1] +[1] +[1] +[1] +[1] +[1] +[1] +[1] +[1] +[1] +[1] +[1] +[1] +[1] +[1] +[1] +[1] +[1] +[1] diff --git a/testsuite/tests/perf/should_run/all.T b/testsuite/tests/perf/should_run/all.T index 5e7e5cf..424bdcb 100644 --- a/testsuite/tests/perf/should_run/all.T +++ b/testsuite/tests/perf/should_run/all.T @@ -445,3 +445,10 @@ test('T9339', only_ways(['normal'])], compile_and_run, ['-O2']) + +test('T12996', + [stats_num_field('bytes allocated', + [ (wordsize(64), 76776, 5) ]), + only_ways(['normal'])], + compile_and_run, + ['-O2']) From git at git.haskell.org Tue Dec 20 21:33:21 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Dec 2016 21:33:21 +0000 (UTC) Subject: [commit: ghc] master: Make CompactionFailed a newtype (8fdb937) Message-ID: <20161220213321.209F83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8fdb937770d8a4c726585def51ac54bf438e9564/ghc >--------------------------------------------------------------- commit 8fdb937770d8a4c726585def51ac54bf438e9564 Author: Ryan Scott Date: Tue Dec 20 16:32:30 2016 -0500 Make CompactionFailed a newtype >--------------------------------------------------------------- 8fdb937770d8a4c726585def51ac54bf438e9564 libraries/base/GHC/IO/Exception.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/base/GHC/IO/Exception.hs b/libraries/base/GHC/IO/Exception.hs index a8d63d3..3c08852 100644 --- a/libraries/base/GHC/IO/Exception.hs +++ b/libraries/base/GHC/IO/Exception.hs @@ -129,12 +129,12 @@ allocationLimitExceeded = toException AllocationLimitExceeded ----- --- |Compaction found an object that cannot be compacted. Functions +-- | Compaction found an object that cannot be compacted. Functions -- cannot be compacted, nor can mutable objects or pinned objects. -- See 'Data.Compact.compact'. -- -- @since 4.10.0.0 -data CompactionFailed = CompactionFailed String +newtype CompactionFailed = CompactionFailed String -- | @since 4.10.0.0 instance Exception CompactionFailed where From git at git.haskell.org Wed Dec 21 06:03:22 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 06:03:22 +0000 (UTC) Subject: [commit: ghc] master: Rewrite Note [Api annotations] for clarity. (574abb7) Message-ID: <20161221060322.767543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/574abb7173d85ee527161cbe36fc0f9535372f0f/ghc >--------------------------------------------------------------- commit 574abb7173d85ee527161cbe36fc0f9535372f0f Author: Edward Z. Yang Date: Tue Dec 20 11:13:23 2016 -0800 Rewrite Note [Api annotations] for clarity. Summary: Based off my understanding of how the moving parts work. Signed-off-by: Edward Z. Yang Test Plan: comments only Reviewers: alanz, mpickering, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2887 >--------------------------------------------------------------- 574abb7173d85ee527161cbe36fc0f9535372f0f compiler/parser/ApiAnnotation.hs | 114 ++++++++++++++++++++------------------- compiler/parser/Lexer.x | 15 ++++++ compiler/parser/Parser.y | 14 ++++- 3 files changed, 88 insertions(+), 55 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 574abb7173d85ee527161cbe36fc0f9535372f0f From git at git.haskell.org Wed Dec 21 10:51:20 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 10:51:20 +0000 (UTC) Subject: [commit: ghc] master: Suppress duplicate .T files (9a29b65) Message-ID: <20161221105120.534EB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9a29b65bda8aed4c5fdbff25866ddf2dd1583210/ghc >--------------------------------------------------------------- commit 9a29b65bda8aed4c5fdbff25866ddf2dd1583210 Author: Gabor Greif Date: Wed Dec 21 11:17:48 2016 +0100 Suppress duplicate .T files As per http://stackoverflow.com/questions/7961363/removing-duplicates-in-lists use the set() function to zap duplicates from the obtained list of .T files. I am using $ python3 --version Python 3.5.1 and strangely findTFiles() returns some .T files twice: -- BEFORE Found 376 .T files... ... ====> Scanning ../../libraries/array/tests/all.T ====> Scanning ../../libraries/array/tests/all.T *** framework failure for T2120(duplicate) There are multiple tests with this name *** framework failure for largeArray(duplicate) There are multiple tests with this name *** framework failure for array001(duplicate) There are multiple tests with this name *** framework failure for T9220(duplicate) There are multiple tests with this name *** framework failure for T229(duplicate) There are multiple tests with this name ... -- AFTER Found 365 .T files... ... ====> Scanning ../../libraries/array/tests/all.T ... Even more strangely 'find' begs to differ: $ find libraries testsuite/tests -name "*.T" | sort | uniq | wc -l 368 >--------------------------------------------------------------- 9a29b65bda8aed4c5fdbff25866ddf2dd1583210 testsuite/driver/runtests.py | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index 28b393a..a30763c 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -255,7 +255,7 @@ print('Timeout is ' + str(config.timeout)) if config.rootdirs == []: config.rootdirs = ['.'] -t_files = list(findTFiles(config.rootdirs)) +t_files = set(findTFiles(config.rootdirs)) print('Found', len(t_files), '.T files...') From git at git.haskell.org Wed Dec 21 10:51:23 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 10:51:23 +0000 (UTC) Subject: [commit: ghc] master: Fix typos (not test relevant) (1771da2) Message-ID: <20161221105123.137763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1771da25fee524c58973c3e6bfbd721f708769c7/ghc >--------------------------------------------------------------- commit 1771da25fee524c58973c3e6bfbd721f708769c7 Author: Gabor Greif Date: Wed Dec 21 11:28:07 2016 +0100 Fix typos (not test relevant) >--------------------------------------------------------------- 1771da25fee524c58973c3e6bfbd721f708769c7 testsuite/driver/testlib.py | 2 +- testsuite/tests/deriving/should_compile/T4816.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 5b582e1..248f276 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -630,7 +630,7 @@ def test(name, setup, func, args): return else: # Note [Mutating config.only] - # config.only is initiallly the set of tests requested by + # config.only is initially the set of tests requested by # the user (via 'make TEST='). We then remove all tests that # we've already seen (in .T files), so that we can later # report on any tests we couldn't find and error out. diff --git a/testsuite/tests/deriving/should_compile/T4816.hs b/testsuite/tests/deriving/should_compile/T4816.hs index 0e81e39..425df4d 100644 --- a/testsuite/tests/deriving/should_compile/T4816.hs +++ b/testsuite/tests/deriving/should_compile/T4816.hs @@ -2,7 +2,7 @@ module T4816 where -data Silly a = Sillly a +data Silly a = Silly a data Baz o = Baz { foo :: o, From git at git.haskell.org Wed Dec 21 14:06:24 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 14:06:24 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #12950 (c469db4) Message-ID: <20161221140624.2C38F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c469db4e5e8814e4a4f1ed7f648514bedb800c25/ghc >--------------------------------------------------------------- commit c469db4e5e8814e4a4f1ed7f648514bedb800c25 Author: Simon Peyton Jones Date: Wed Dec 21 12:26:12 2016 +0000 Test Trac #12950 >--------------------------------------------------------------- c469db4e5e8814e4a4f1ed7f648514bedb800c25 testsuite/tests/deSugar/should_compile/T12950.hs | 17 +++++++++++++++++ testsuite/tests/deSugar/should_compile/all.T | 1 + 2 files changed, 18 insertions(+) diff --git a/testsuite/tests/deSugar/should_compile/T12950.hs b/testsuite/tests/deSugar/should_compile/T12950.hs new file mode 100644 index 0000000..a7fd2e3 --- /dev/null +++ b/testsuite/tests/deSugar/should_compile/T12950.hs @@ -0,0 +1,17 @@ +{-# LANGUAGE TypeFamilies #-} + +{-# OPTIONS_GHC -O #-} + +module T12950 where + +class C a where + type TF a; m :: a -> TF a + +instance C Int where + type TF Int = String; m = show + +overloaded :: C a => a -> (a,TF a) +{-# INLINABLE overloaded #-} +overloaded a = (a,m a) + +{-# SPECIALIZE overloaded :: Int -> (Int,TF Int) #-} diff --git a/testsuite/tests/deSugar/should_compile/all.T b/testsuite/tests/deSugar/should_compile/all.T index a731602..6d026db 100644 --- a/testsuite/tests/deSugar/should_compile/all.T +++ b/testsuite/tests/deSugar/should_compile/all.T @@ -106,3 +106,4 @@ test('DsStrictWarn', normal, compile, ['']) test('T10662', normal, compile, ['-Wall']) test('T11414', normal, compile, ['']) test('T12944', normal, compile, ['']) +test('T12950', normal, compile, ['']) From git at git.haskell.org Wed Dec 21 14:06:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 14:06:26 +0000 (UTC) Subject: [commit: ghc] master: Move typeSize/coercionSize into TyCoRep (c66dd05) Message-ID: <20161221140626.D745F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c66dd05c8d02e2b7df825ed2f13b79fb3a16ab58/ghc >--------------------------------------------------------------- commit c66dd05c8d02e2b7df825ed2f13b79fb3a16ab58 Author: Simon Peyton Jones Date: Wed Dec 21 11:24:25 2016 +0000 Move typeSize/coercionSize into TyCoRep While investigating something else I found that 'typeSize' was allocating like crazy. Stupid becuase it should allocate precisely nothing!! Turned out that it was because typeSize and coercionSize were mutually recursive across module boundaries, and so could not benefit from the CPR property. To fix this I moved them both into TyCoRep. It's not critical (because typeSize is really only used in debug mode, but I tripped over and example (T5642) in which typeSize was one of the biggest single allocators in all of GHC. And it's easy to fix, so I did. >--------------------------------------------------------------- c66dd05c8d02e2b7df825ed2f13b79fb3a16ab58 compiler/types/Coercion.hs | 24 ----------------- compiler/types/Coercion.hs-boot | 1 - compiler/types/TyCoRep.hs | 60 ++++++++++++++++++++++++++++++++++++++++- compiler/types/Type.hs | 21 --------------- 4 files changed, 59 insertions(+), 47 deletions(-) diff --git a/compiler/types/Coercion.hs b/compiler/types/Coercion.hs index 6545ec0..0adadc3 100644 --- a/compiler/types/Coercion.hs +++ b/compiler/types/Coercion.hs @@ -150,30 +150,6 @@ setCoVarUnique = setVarUnique setCoVarName :: CoVar -> Name -> CoVar setCoVarName = setVarName -coercionSize :: Coercion -> Int -coercionSize (Refl _ ty) = typeSize ty -coercionSize (TyConAppCo _ _ args) = 1 + sum (map coercionSize args) -coercionSize (AppCo co arg) = coercionSize co + coercionSize arg -coercionSize (ForAllCo _ h co) = 1 + coercionSize co + coercionSize h -coercionSize (CoVarCo _) = 1 -coercionSize (AxiomInstCo _ _ args) = 1 + sum (map coercionSize args) -coercionSize (UnivCo p _ t1 t2) = 1 + provSize p + typeSize t1 + typeSize t2 -coercionSize (SymCo co) = 1 + coercionSize co -coercionSize (TransCo co1 co2) = 1 + coercionSize co1 + coercionSize co2 -coercionSize (NthCo _ co) = 1 + coercionSize co -coercionSize (LRCo _ co) = 1 + coercionSize co -coercionSize (InstCo co arg) = 1 + coercionSize co + coercionSize arg -coercionSize (CoherenceCo c1 c2) = 1 + coercionSize c1 + coercionSize c2 -coercionSize (KindCo co) = 1 + coercionSize co -coercionSize (SubCo co) = 1 + coercionSize co -coercionSize (AxiomRuleCo _ cs) = 1 + sum (map coercionSize cs) - -provSize :: UnivCoProvenance -> Int -provSize UnsafeCoerceProv = 1 -provSize (PhantomProv co) = 1 + coercionSize co -provSize (ProofIrrelProv co) = 1 + coercionSize co -provSize (PluginProv _) = 1 -provSize (HoleProv h) = pprPanic "provSize hits a hole" (ppr h) {- %************************************************************************ diff --git a/compiler/types/Coercion.hs-boot b/compiler/types/Coercion.hs-boot index 807d855..8ba9295 100644 --- a/compiler/types/Coercion.hs-boot +++ b/compiler/types/Coercion.hs-boot @@ -39,7 +39,6 @@ mkCoercionType :: Role -> Type -> Type -> Type data LiftingContext liftCoSubst :: Role -> LiftingContext -> Type -> Coercion -coercionSize :: Coercion -> Int seqCo :: Coercion -> () coercionKind :: Coercion -> Pair Type diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index c007321..63aba3c 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -123,7 +123,10 @@ module TyCoRep ( tidyTopType, tidyKind, tidyCo, tidyCos, - tidyTyVarBinder, tidyTyVarBinders + tidyTyVarBinder, tidyTyVarBinders, + + -- * Sizes + typeSize, coercionSize, provSize ) where #include "HsVersions.h" @@ -2743,3 +2746,58 @@ tidyCo env@(_, subst) co tidyCos :: TidyEnv -> [Coercion] -> [Coercion] tidyCos env = map (tidyCo env) + + +{- ********************************************************************* +* * + typeSize, coercionSize +* * +********************************************************************* -} + +-- NB: We put typeSize/coercionSize here because they are mutually +-- recursive, and have the CPR property. If we have mutual +-- recursion across a hi-boot file, we don't get the CPR property +-- and these functions allocate a tremendous amount of rubbish. +-- It's not critical (because typeSize is really only used in +-- debug mode, but I tripped over and example (T5642) in which +-- typeSize was one of the biggest single allocators in all of GHC. +-- And it's easy to fix, so I did. + +-- NB: typeSize does not respect `eqType`, in that two types that +-- are `eqType` may return different sizes. This is OK, because this +-- function is used only in reporting, not decision-making. + +typeSize :: Type -> Int +typeSize (LitTy {}) = 1 +typeSize (TyVarTy {}) = 1 +typeSize (AppTy t1 t2) = typeSize t1 + typeSize t2 +typeSize (FunTy t1 t2) = typeSize t1 + typeSize t2 +typeSize (ForAllTy (TvBndr tv _) t) = typeSize (tyVarKind tv) + typeSize t +typeSize (TyConApp _ ts) = 1 + sum (map typeSize ts) +typeSize (CastTy ty co) = typeSize ty + coercionSize co +typeSize (CoercionTy co) = coercionSize co + +coercionSize :: Coercion -> Int +coercionSize (Refl _ ty) = typeSize ty +coercionSize (TyConAppCo _ _ args) = 1 + sum (map coercionSize args) +coercionSize (AppCo co arg) = coercionSize co + coercionSize arg +coercionSize (ForAllCo _ h co) = 1 + coercionSize co + coercionSize h +coercionSize (CoVarCo _) = 1 +coercionSize (AxiomInstCo _ _ args) = 1 + sum (map coercionSize args) +coercionSize (UnivCo p _ t1 t2) = 1 + provSize p + typeSize t1 + typeSize t2 +coercionSize (SymCo co) = 1 + coercionSize co +coercionSize (TransCo co1 co2) = 1 + coercionSize co1 + coercionSize co2 +coercionSize (NthCo _ co) = 1 + coercionSize co +coercionSize (LRCo _ co) = 1 + coercionSize co +coercionSize (InstCo co arg) = 1 + coercionSize co + coercionSize arg +coercionSize (CoherenceCo c1 c2) = 1 + coercionSize c1 + coercionSize c2 +coercionSize (KindCo co) = 1 + coercionSize co +coercionSize (SubCo co) = 1 + coercionSize co +coercionSize (AxiomRuleCo _ cs) = 1 + sum (map coercionSize cs) + +provSize :: UnivCoProvenance -> Int +provSize UnsafeCoerceProv = 1 +provSize (PhantomProv co) = 1 + coercionSize co +provSize (ProofIrrelProv co) = 1 + coercionSize co +provSize (PluginProv _) = 1 +provSize (HoleProv h) = pprPanic "provSize hits a hole" (ppr h) diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index 1e429ef..14aa8fd 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -1733,27 +1733,6 @@ predTypeEqRel ty {- %************************************************************************ %* * - Size -* * -************************************************************************ --} - --- NB: This function does not respect `eqType`, in that two types that --- are `eqType` may return different sizes. This is OK, because this --- function is used only in reporting, not decision-making. -typeSize :: Type -> Int -typeSize (LitTy {}) = 1 -typeSize (TyVarTy {}) = 1 -typeSize (AppTy t1 t2) = typeSize t1 + typeSize t2 -typeSize (FunTy t1 t2) = typeSize t1 + typeSize t2 -typeSize (ForAllTy (TvBndr tv _) t) = typeSize (tyVarKind tv) + typeSize t -typeSize (TyConApp _ ts) = 1 + sum (map typeSize ts) -typeSize (CastTy ty co) = typeSize ty + coercionSize co -typeSize (CoercionTy co) = coercionSize co - -{- -%************************************************************************ -%* * Well-scoped tyvars * * ************************************************************************ From git at git.haskell.org Wed Dec 21 14:06:29 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 14:06:29 +0000 (UTC) Subject: [commit: ghc] master: Add INLINE pragamas on Traversable default methods (d250d49) Message-ID: <20161221140629.906DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d250d493d1dbe0bcfb19122ab3444c9450babdca/ghc >--------------------------------------------------------------- commit d250d493d1dbe0bcfb19122ab3444c9450babdca Author: Simon Peyton Jones Date: Wed Dec 21 11:38:50 2016 +0000 Add INLINE pragamas on Traversable default methods I discovered, when debugging a performance regression in the compiler, that the list instance of mapM was not being inlined at call sites, with terrible runtime costs. It turned out that this was a serious (but not entirely obvious) omission of an INLINE pragmas in the class declaration for Traversable. This patch fixes it. I reproduce below the Note [Inline default methods], which I wrote at some length. We may well want to apply the same fix in other class declarations whose default methods are often used. {- Note [Inline default methods] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider class ... => Traversable t where ... mapM :: Monad m => (a -> m b) -> t a -> m (t b) mapM = traverse -- Default method instance Traversable [] where {-# INLINE traverse #-} traverse = ...code for traverse on lists ... This gives rise to a list-instance of mapM looking like this $fTraversable[]_$ctaverse = ...code for traverse on lists... {-# INLINE $fTraversable[]_$ctaverse #-} $fTraversable[]_$cmapM = $fTraversable[]_$ctraverse Now the $ctraverse obediently inlines into the RHS of $cmapM, /but/ that's all! We get $fTraversable[]_$cmapM = ...code for traverse on lists... with NO INLINE pragma! This happens even though 'traverse' had an INLINE pragma becuase the author knew it should be inlined pretty vigorously. Indeed, it turned out that the rhs of $cmapM was just too big to inline, so all uses of mapM on lists used a terribly inefficient dictionary-passing style, because of its 'Monad m =>' type. Disaster! Solution: add an INLINE pragma on the default method: class ... => Traversable t where ... mapM :: Monad m => (a -> m b) -> t a -> m (t b) {-# INLINE mapM #-} -- VERY IMPORTANT! mapM = traverse >--------------------------------------------------------------- d250d493d1dbe0bcfb19122ab3444c9450babdca libraries/base/Data/Traversable.hs | 45 ++++++++++++++++++++++++++++++++++++++ 1 file changed, 45 insertions(+) diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs index 6f503b7..635fcde 100644 --- a/libraries/base/Data/Traversable.hs +++ b/libraries/base/Data/Traversable.hs @@ -157,26 +157,71 @@ class (Functor t, Foldable t) => Traversable t where -- from left to right, and collect the results. For a version that ignores -- the results see 'Data.Foldable.traverse_'. traverse :: Applicative f => (a -> f b) -> t a -> f (t b) + {-# INLINE traverse #-} -- See Note [Inline default methods] traverse f = sequenceA . fmap f -- | Evaluate each action in the structure from left to right, and -- and collect the results. For a version that ignores the results -- see 'Data.Foldable.sequenceA_'. sequenceA :: Applicative f => t (f a) -> f (t a) + {-# INLINE sequenceA #-} -- See Note [Inline default methods] sequenceA = traverse id -- | Map each element of a structure to a monadic action, evaluate -- these actions from left to right, and collect the results. For -- a version that ignores the results see 'Data.Foldable.mapM_'. mapM :: Monad m => (a -> m b) -> t a -> m (t b) + {-# INLINE mapM #-} -- See Note [Inline default methods] mapM = traverse -- | Evaluate each monadic action in the structure from left to -- right, and collect the results. For a version that ignores the -- results see 'Data.Foldable.sequence_'. sequence :: Monad m => t (m a) -> m (t a) + {-# INLINE sequence #-} -- See Note [Inline default methods] sequence = sequenceA +{- Note [Inline default methods] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider + + class ... => Traversable t where + ... + mapM :: Monad m => (a -> m b) -> t a -> m (t b) + mapM = traverse -- Default method + + instance Traversable [] where + {-# INLINE traverse #-} + traverse = ...code for traverse on lists ... + +This gives rise to a list-instance of mapM looking like this + + $fTraversable[]_$ctaverse = ...code for traverse on lists... + {-# INLINE $fTraversable[]_$ctaverse #-} + $fTraversable[]_$cmapM = $fTraversable[]_$ctraverse + +Now the $ctraverse obediently inlines into the RHS of $cmapM, /but/ +that's all! We get + + $fTraversable[]_$cmapM = ...code for traverse on lists... + +with NO INLINE pragma! This happens even though 'traverse' had an +INLINE pragma becuase the author knew it should be inlined pretty +vigorously. + +Indeed, it turned out that the rhs of $cmapM was just too big to +inline, so all uses of mapM on lists used a terribly inefficient +dictionary-passing style, because of its 'Monad m =>' type. Disaster! + +Solution: add an INLINE pragma on the default method: + + class ... => Traversable t where + ... + mapM :: Monad m => (a -> m b) -> t a -> m (t b) + {-# INLINE mapM #-} -- VERY IMPORTANT! + mapM = traverse +-} + -- instances for Prelude types -- | @since 2.01 From git at git.haskell.org Wed Dec 21 14:06:32 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 14:06:32 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #12968, plus some comments (f97d489) Message-ID: <20161221140632.BAF803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f97d489911aabd2396f5df87efd7d1d164017142/ghc >--------------------------------------------------------------- commit f97d489911aabd2396f5df87efd7d1d164017142 Author: Simon Peyton Jones Date: Mon Dec 19 15:05:57 2016 +0000 Test Trac #12968, plus some comments >--------------------------------------------------------------- f97d489911aabd2396f5df87efd7d1d164017142 compiler/rename/RnNames.hs | 2 ++ compiler/typecheck/TcRnDriver.hs | 3 +++ testsuite/tests/patsyn/should_compile/T12968.hs | 14 ++++++++++++++ testsuite/tests/patsyn/should_compile/all.T | 1 + 4 files changed, 20 insertions(+) diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs index 8da11be..8a7529d 100644 --- a/compiler/rename/RnNames.hs +++ b/compiler/rename/RnNames.hs @@ -1147,6 +1147,8 @@ warnUnusedImportDecls gbl_env printMinimalImports usage } -- | Warn the user about top level binders that lack type signatures. +-- Called /after/ type inference, so that we can report the +-- inferred type of the function warnMissingSignatures :: TcGblEnv -> RnM () warnMissingSignatures gbl_env = do { let exports = availsToNameSet (tcg_exports gbl_env) diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index ad49ca0..a1b559c 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -267,6 +267,9 @@ tcRnModuleTcRnM hsc_env hsc_src tcg_env <- return (tcg_env { tcg_doc_hdr = maybe_doc_hdr }) ; -- Report unused names + -- Do this /after/ type inference, so that when reporting + -- a function with no type signature we can give the + -- inferred type reportUnusedNames export_ies tcg_env ; -- add extra source files to tcg_dependent_files diff --git a/testsuite/tests/patsyn/should_compile/T12968.hs b/testsuite/tests/patsyn/should_compile/T12968.hs new file mode 100644 index 0000000..9d38500 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T12968.hs @@ -0,0 +1,14 @@ +{-# LANGUAGE TypeInType, GADTs, ScopedTypeVariables, PatternSynonyms, + ViewPatterns #-} + +module T12968 where + +data TypeRep (a :: k) + +data TRAppG (fun :: k2) where + TRAppG :: forall k1 (a :: k1 -> k2) (b :: k1) . TypeRep a -> TypeRep b -> TRAppG (a b) + +pattern TRApp :: forall k2 (fun :: k2). () + => forall k1 (a :: k1 -> k2) (b :: k1). (fun ~ a b) + => TypeRep a -> TypeRep b -> TypeRep fun +pattern TRApp a b <- ((undefined :: TypeRep fun -> TRAppG fun) -> TRAppG a b) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index 1952672..6bd1461 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -62,3 +62,4 @@ test('T11987', normal, multimod_compile, ['T11987', '-v0']) test('T12615', normal, compile, ['']) test('T12698', normal, compile, ['']) test('T12746', normal, multi_compile, ['T12746', [('T12746A.hs', '-c')],'-v0']) +test('T12968', normal, compile, ['']) From git at git.haskell.org Wed Dec 21 14:06:35 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 14:06:35 +0000 (UTC) Subject: [commit: ghc] master: Never apply worker/wrapper to DFuns (c48595e) Message-ID: <20161221140635.71B053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c48595eef2bca6d91ec0a649839f8066f269e6a4/ghc >--------------------------------------------------------------- commit c48595eef2bca6d91ec0a649839f8066f269e6a4 Author: Simon Peyton Jones Date: Wed Dec 21 12:22:00 2016 +0000 Never apply worker/wrapper to DFuns While fixing Trac #12444 I found an occasion on which we applied worker/wrapper to a DFunId. This is bad: it destroys the magic DFunUnfolding. This patch is a minor refactoring that stops this corner case happening, and tidies up the code a bit too. >--------------------------------------------------------------- c48595eef2bca6d91ec0a649839f8066f269e6a4 compiler/coreSyn/CoreUnfold.hs | 74 ++++++++++++++++++++++++------------------ compiler/stranal/WorkWrap.hs | 10 ++---- 2 files changed, 46 insertions(+), 38 deletions(-) diff --git a/compiler/coreSyn/CoreUnfold.hs b/compiler/coreSyn/CoreUnfold.hs index 7faee63..a601539 100644 --- a/compiler/coreSyn/CoreUnfold.hs +++ b/compiler/coreSyn/CoreUnfold.hs @@ -944,40 +944,52 @@ smallEnoughToInline _ _ = False ---------------- -certainlyWillInline :: DynFlags -> Unfolding -> Maybe Unfolding + +certainlyWillInline :: DynFlags -> IdInfo -> Maybe Unfolding -- Sees if the unfolding is pretty certain to inline -- If so, return a *stable* unfolding for it, that will always inline -certainlyWillInline dflags unf@(CoreUnfolding { uf_guidance = guidance, uf_tmpl = expr }) - = case guidance of - UnfNever -> Nothing - UnfWhen {} -> Just (unf { uf_src = InlineStable }) - - -- The UnfIfGoodArgs case seems important. If we w/w small functions - -- binary sizes go up by 10%! (This is with SplitObjs.) I'm not totally - -- sure whyy. - UnfIfGoodArgs { ug_size = size, ug_args = args } - | not (null args) -- See Note [certainlyWillInline: be careful of thunks] - , let arity = length args - , size - (10 * (arity + 1)) <= ufUseThreshold dflags - -> Just (unf { uf_src = InlineStable - , uf_guidance = UnfWhen { ug_arity = arity - , ug_unsat_ok = unSaturatedOk - , ug_boring_ok = inlineBoringOk expr } }) - -- Note the "unsaturatedOk". A function like f = \ab. a - -- will certainly inline, even if partially applied (f e), so we'd - -- better make sure that the transformed inlining has the same property - - _ -> Nothing - -certainlyWillInline _ unf@(DFunUnfolding {}) - = Just unf - -certainlyWillInline _ _ - = Nothing +certainlyWillInline dflags fn_info + = case unfoldingInfo fn_info of + CoreUnfolding { uf_tmpl = e, uf_guidance = g } + | loop_breaker -> Nothing -- Won't inline, so try w/w + | otherwise -> do_cunf e g -- Depends on size, so look at that -{- -Note [certainlyWillInline: be careful of thunks] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + DFunUnfolding {} -> Just fn_unf -- Don't w/w DFuns; it never makes sense + -- to do so, and even if it is currently a + -- loop breaker, it may not be later + + _other_unf -> Nothing + + where + loop_breaker = isStrongLoopBreaker (occInfo fn_info) + fn_unf = unfoldingInfo fn_info + + do_cunf :: CoreExpr -> UnfoldingGuidance -> Maybe Unfolding + do_cunf _ UnfNever = Nothing + do_cunf _ (UnfWhen {}) = Just (fn_unf { uf_src = InlineStable }) + -- INLINE functions have UnfWhen + + -- The UnfIfGoodArgs case seems important. If we w/w small functions + -- binary sizes go up by 10%! (This is with SplitObjs.) + -- I'm not totally sure why. + -- INLINABLE functions come via this path + -- See Note [certainlyWillInline: INLINABLE] + do_cunf expr (UnfIfGoodArgs { ug_size = size, ug_args = args }) + | not (null args) -- See Note [certainlyWillInline: be careful of thunks] + , let arity = length args + , size - (10 * (arity + 1)) <= ufUseThreshold dflags + = Just (fn_unf { uf_src = InlineStable + , uf_guidance = UnfWhen { ug_arity = arity + , ug_unsat_ok = unSaturatedOk + , ug_boring_ok = inlineBoringOk expr } }) + -- Note the "unsaturatedOk". A function like f = \ab. a + -- will certainly inline, even if partially applied (f e), so we'd + -- better make sure that the transformed inlining has the same property + | otherwise + = Nothing + +{- Note [certainlyWillInline: be careful of thunks] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Don't claim that thunks will certainly inline, because that risks work duplication. Even if the work duplication is not great (eg is_cheap holds), it can make a big difference in an inner loop In Trac #5623 we diff --git a/compiler/stranal/WorkWrap.hs b/compiler/stranal/WorkWrap.hs index 2db3a71..d50bb22 100644 --- a/compiler/stranal/WorkWrap.hs +++ b/compiler/stranal/WorkWrap.hs @@ -289,12 +289,10 @@ tryWW dflags fam_envs is_rec fn_id rhs -- being inlined at a call site. = return [ (new_fn_id, rhs) ] - | not loop_breaker - , Just stable_unf <- certainlyWillInline dflags fn_unf + | Just stable_unf <- certainlyWillInline dflags fn_info = return [ (fn_id `setIdUnfolding` stable_unf, rhs) ] - -- Note [Don't w/w inline small non-loop-breaker, or INLINE, things] - -- NB: use idUnfolding because we don't want to apply - -- this criterion to a loop breaker! + -- See Note [Don't w/w INLINE things] + -- See Note [Don't w/w inline small non-loop-breaker things] | is_fun = splitFun dflags fam_envs new_fn_id fn_info wrap_dmds res_info rhs @@ -306,10 +304,8 @@ tryWW dflags fam_envs is_rec fn_id rhs = return [ (new_fn_id, rhs) ] where - loop_breaker = isStrongLoopBreaker (occInfo fn_info) fn_info = idInfo fn_id inline_act = inlinePragmaActivation (inlinePragInfo fn_info) - fn_unf = unfoldingInfo fn_info (wrap_dmds, res_info) = splitStrictSig (strictnessInfo fn_info) new_fn_id = zapIdUsedOnceInfo (zapIdUsageEnvInfo fn_id) From git at git.haskell.org Wed Dec 21 14:06:39 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 14:06:39 +0000 (UTC) Subject: [commit: ghc] master: Fix 'SPECIALISE instance' (1a4c04b) Message-ID: <20161221140639.5B2783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1a4c04b13a695a530ee24835a7550a8c9ed2d37a/ghc >--------------------------------------------------------------- commit 1a4c04b13a695a530ee24835a7550a8c9ed2d37a Author: Simon Peyton Jones Date: Wed Dec 21 12:24:41 2016 +0000 Fix 'SPECIALISE instance' Trac #12944 showed that the DsBinds code that implemented a SPECIALISE pragma was inadequate if the constraints solving added let-bindings for dictionaries. The result was that we ended up with an unbound dictionary in a DFunUnfolding -- and Lint didn't even check for that! Fixing this was not entirely straightforward * In DsBinds.dsSpec we use a new function TcEvidence.collectHsWrapBinders to pick off the lambda binders from the HsWapper * dsWrapper now returns a (CoreExpr -> CoreExpr) function * CoreUnfold.specUnfolding now takes a (CoreExpr -> CoreExpr) function it can use to specialise the unfolding. On the whole the code is simpler than before. >--------------------------------------------------------------- 1a4c04b13a695a530ee24835a7550a8c9ed2d37a compiler/coreSyn/CoreUnfold.hs | 63 +++++++------- compiler/deSugar/DsArrows.hs | 4 +- compiler/deSugar/DsBinds.hs | 98 ++++++++++++---------- compiler/deSugar/DsExpr.hs | 11 ++- compiler/deSugar/Match.hs | 5 +- compiler/specialise/Specialise.hs | 29 +++---- compiler/typecheck/TcEvidence.hs | 19 ++++- compiler/typecheck/TcInstDcls.hs | 2 +- testsuite/tests/deSugar/should_compile/T12944.hs | 36 ++++++++ testsuite/tests/deSugar/should_compile/all.T | 1 + .../tests/indexed-types/should_compile/T12444a.hs | 12 +++ 11 files changed, 182 insertions(+), 98 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1a4c04b13a695a530ee24835a7550a8c9ed2d37a From git at git.haskell.org Wed Dec 21 14:06:43 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 14:06:43 +0000 (UTC) Subject: [commit: ghc] master: Don't eta-expand in stable unfoldings (e07ad4d) Message-ID: <20161221140643.223A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e07ad4db75885f6e3ff82aa3343999f2af39a16d/ghc >--------------------------------------------------------------- commit e07ad4db75885f6e3ff82aa3343999f2af39a16d Author: Simon Peyton Jones Date: Wed Dec 21 12:01:32 2016 +0000 Don't eta-expand in stable unfoldings See SimplUtils Note [No eta expansion in stable unfoldings], and Trac #9509 for an excellend diagnosis by Nick Frisby >--------------------------------------------------------------- e07ad4db75885f6e3ff82aa3343999f2af39a16d compiler/simplCore/SimplUtils.hs | 43 +++++++++++++++++----- compiler/simplCore/Simplify.hs | 6 +-- testsuite/tests/simplCore/should_compile/Makefile | 8 ++++ testsuite/tests/simplCore/should_compile/T9509.hs | 5 +++ .../tests/simplCore/should_compile/T9509.stdout | 1 + testsuite/tests/simplCore/should_compile/T9509a.hs | 10 +++++ testsuite/tests/simplCore/should_compile/all.T | 4 ++ 7 files changed, 64 insertions(+), 13 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e07ad4db75885f6e3ff82aa3343999f2af39a16d From git at git.haskell.org Wed Dec 21 14:06:46 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 14:06:46 +0000 (UTC) Subject: [commit: ghc] master: Add note for rebindable syntax of [a..b] (c73a982) Message-ID: <20161221140646.1A67F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c73a982bc49a234a030cea2496b70829c98b1e10/ghc >--------------------------------------------------------------- commit c73a982bc49a234a030cea2496b70829c98b1e10 Author: Simon Peyton Jones Date: Mon Dec 19 15:06:34 2016 +0000 Add note for rebindable syntax of [a..b] See Trac #12969 >--------------------------------------------------------------- c73a982bc49a234a030cea2496b70829c98b1e10 docs/users_guide/glasgow_exts.rst | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index b28edf7..919ec7d 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -1443,6 +1443,10 @@ not the Prelude versions: functions must match the Prelude types very closely. Details are in flux; if you want to use this, ask! +- List notation, such as ``[x,y]`` or ``[m..n]`` can also be treated + via rebindable syntax if you use `-XOverloadedLists`; + see :ref:`overloaded-lists`. + :ghc-flag:`-XRebindableSyntax` implies :ghc-flag:`-XNoImplicitPrelude`. In all cases (apart from arrow notation), the static semantics should be From git at git.haskell.org Wed Dec 21 14:06:48 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 14:06:48 +0000 (UTC) Subject: [commit: ghc] master: Move InId/OutId to CoreSyn (05d233e) Message-ID: <20161221140648.E4DB43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/05d233e8e18284cb98dc320bf58191ba4d86c754/ghc >--------------------------------------------------------------- commit 05d233e8e18284cb98dc320bf58191ba4d86c754 Author: Simon Peyton Jones Date: Wed Dec 21 12:13:11 2016 +0000 Move InId/OutId to CoreSyn It turned out that many different modules defined the same type synonyms (InId, OutId, InType, OutType, etc) for the same purpose. This patch is refactoring only: it moves all those definitions to CoreSyn. >--------------------------------------------------------------- 05d233e8e18284cb98dc320bf58191ba4d86c754 compiler/coreSyn/CoreLint.hs | 16 ++----------- compiler/coreSyn/CoreSubst.hs | 9 +------ compiler/coreSyn/CoreSyn.hs | 49 +++++++++++++++++++++++++++++++++++++-- compiler/simplCore/CSE.hs | 11 +-------- compiler/simplCore/SetLevels.hs | 5 ---- compiler/simplCore/SimplEnv.hs | 34 --------------------------- compiler/simplStg/UnariseStg.hs | 2 -- compiler/specialise/SpecConstr.hs | 9 ------- 8 files changed, 51 insertions(+), 84 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 05d233e8e18284cb98dc320bf58191ba4d86c754 From git at git.haskell.org Wed Dec 21 14:06:51 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 14:06:51 +0000 (UTC) Subject: [commit: ghc] master: Lint DFunUnfoldings (0a18231) Message-ID: <20161221140651.A1C043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0a18231b9c62c9f773a5c74f7cc290416fbbb655/ghc >--------------------------------------------------------------- commit 0a18231b9c62c9f773a5c74f7cc290416fbbb655 Author: Simon Peyton Jones Date: Mon Dec 19 15:04:51 2016 +0000 Lint DFunUnfoldings Previously we simply failed to Lint these DFunUnfoldings, which led to a very delayed error message for Trac #12944 >--------------------------------------------------------------- 0a18231b9c62c9f773a5c74f7cc290416fbbb655 compiler/coreSyn/CoreLint.hs | 16 ++++++++++++++-- 1 file changed, 14 insertions(+), 2 deletions(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index 8f47d5e..345e4b5 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -563,7 +563,7 @@ lintRhs rhs -- imitate @lintCoreExpr (App ...)@ [] -> do fun_ty <- lintCoreExpr fun - addLoc (AnExpr rhs') $ foldM lintCoreArg fun_ty args + addLoc (AnExpr rhs') $ lintCoreArgs fun_ty args -- Rejects applications of the data constructor @StaticPtr@ if it finds any. lintRhs rhs = lintCoreExpr rhs @@ -572,6 +572,14 @@ lintIdUnfolding bndr bndr_ty (CoreUnfolding { uf_tmpl = rhs, uf_src = src }) | isStableSource src = do { ty <- lintCoreExpr rhs ; ensureEqTys bndr_ty ty (mkRhsMsg bndr (text "unfolding") ty) } + +lintIdUnfolding bndr bndr_ty (DFunUnfolding { df_con = con, df_bndrs = bndrs + , df_args = args }) + = do { ty <- lintBinders bndrs $ \ bndrs' -> + do { res_ty <- lintCoreArgs (dataConRepType con) args + ; return (mkLamTypes bndrs' res_ty) } + ; ensureEqTys bndr_ty ty (mkRhsMsg bndr (text "dfun unfolding") ty) } + lintIdUnfolding _ _ _ = return () -- Do not Lint unstable unfoldings, because that leads -- to exponential behaviour; c.f. CoreFVs.idUnfoldingVars @@ -694,7 +702,7 @@ lintCoreExpr e@(App _ _) _ -> go where go = do { fun_ty <- lintCoreExpr fun - ; addLoc (AnExpr e) $ foldM lintCoreArg fun_ty args } + ; addLoc (AnExpr e) $ lintCoreArgs fun_ty args } (fun, args) = collectArgs e @@ -791,6 +799,10 @@ The basic version of these functions checks that the argument is a subtype of the required type, as one would expect. -} + +lintCoreArgs :: OutType -> [CoreArg] -> LintM OutType +lintCoreArgs fun_ty args = foldM lintCoreArg fun_ty args + lintCoreArg :: OutType -> CoreArg -> LintM OutType lintCoreArg fun_ty (Type arg_ty) = do { checkL (not (isCoercionTy arg_ty)) From git at git.haskell.org Wed Dec 21 14:06:54 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 14:06:54 +0000 (UTC) Subject: [commit: ghc] master: Improved perf for T12227 (74033c4) Message-ID: <20161221140654.666903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/74033c46d31874e7b1cccc9482cba22158121fa4/ghc >--------------------------------------------------------------- commit 74033c46d31874e7b1cccc9482cba22158121fa4 Author: Simon Peyton Jones Date: Wed Dec 21 14:03:53 2016 +0000 Improved perf for T12227 Improved compiler allocations by abut 5%. It comes from one of 1a4c04b1 Fix 'SPECIALISE instance' c48595ee Never apply worker/wrapper to DFuns 05d233e8 Move InId/OutId to CoreSyn e07ad4db Don't eta-expand in stable unfoldings d250d493 Add INLINE pragamas on Traversable default methods c66dd05c Move typeSize/coercionSize into TyCoRep I think d250d493. But it's good anyway. >--------------------------------------------------------------- 74033c46d31874e7b1cccc9482cba22158121fa4 testsuite/tests/perf/compiler/all.T | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index ec59805..75e361d 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -866,9 +866,11 @@ test('T10547', test('T12227', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 1822822016, 5), + [(wordsize(64), 1715827784, 5), # 2016-07-11 5650186880 (Windows) before fix for #12227 # 2016-07-11 1822822016 (Windows) after fix for #12227 + # 2016-12-20 1715827784 after d250d493 (INLINE in Traversable dms) + # (or thereabouts in the commit history) ]), ], compile, From git at git.haskell.org Wed Dec 21 16:47:56 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 16:47:56 +0000 (UTC) Subject: [commit: ghc] master: Fix a forward reference to a Note (ccc918c) Message-ID: <20161221164756.55BA93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ccc918cdc8b2d147c4dbc29bfc87c058862a97cd/ghc >--------------------------------------------------------------- commit ccc918cdc8b2d147c4dbc29bfc87c058862a97cd Author: Ryan Scott Date: Wed Dec 21 11:40:06 2016 -0500 Fix a forward reference to a Note >--------------------------------------------------------------- ccc918cdc8b2d147c4dbc29bfc87c058862a97cd compiler/hsSyn/Convert.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/hsSyn/Convert.hs b/compiler/hsSyn/Convert.hs index efd0428..7749265 100644 --- a/compiler/hsSyn/Convert.hs +++ b/compiler/hsSyn/Convert.hs @@ -1363,8 +1363,8 @@ cvtInjectivityAnnotation (TH.InjectivityAnn annLHS annRHS) cvtPatSynSigTy :: TH.Type -> CvtM (LHsType RdrName) -- pattern synonym types are of peculiar shapes, which is why we treat --- them separately from regular types; see NOTE [Pattern synonym --- signatures and Template Haskell] +-- them separately from regular types; +-- see Note [Pattern synonym type signatures and Template Haskell] cvtPatSynSigTy (ForallT univs reqs (ForallT exis provs ty)) | null exis, null provs = cvtType (ForallT univs reqs ty) | null univs, null reqs = do { l <- getL From git at git.haskell.org Wed Dec 21 16:47:59 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 16:47:59 +0000 (UTC) Subject: [commit: ghc] master: Disambiguate two Notes with identical names (2189239) Message-ID: <20161221164759.11FA33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2189239872322dc363cc5f82e14ab5fb1a6d5b8c/ghc >--------------------------------------------------------------- commit 2189239872322dc363cc5f82e14ab5fb1a6d5b8c Author: Ryan Scott Date: Wed Dec 21 11:44:04 2016 -0500 Disambiguate two Notes with identical names It turns out there were two Notes in the GHC codebase named [Pattern synonym signatures]. To avoid confusion, I gave one Note a slightly different name. >--------------------------------------------------------------- 2189239872322dc363cc5f82e14ab5fb1a6d5b8c compiler/basicTypes/PatSyn.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/PatSyn.hs b/compiler/basicTypes/PatSyn.hs index 774879e..823c838 100644 --- a/compiler/basicTypes/PatSyn.hs +++ b/compiler/basicTypes/PatSyn.hs @@ -48,7 +48,7 @@ import Data.List -- | Pattern Synonym -- -- See Note [Pattern synonym representation] --- See Note [Pattern synonym signatures] +-- See Note [Pattern synonym signature contexts] data PatSyn = MkPatSyn { psName :: Name, @@ -107,7 +107,7 @@ data PatSyn -- See Note [Builder for pattern synonyms with unboxed type] } -{- Note [Pattern synonym signatures] +{- Note [Pattern synonym signature contexts] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ In a pattern synonym signature we write pattern P :: req => prov => t1 -> ... tn -> res_ty From git at git.haskell.org Wed Dec 21 16:49:27 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 16:49:27 +0000 (UTC) Subject: [commit: ghc] master: Support for abi-depends for computing shadowing. (ee4e165) Message-ID: <20161221164927.2786F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ee4e1654c31b9c6f6ad9b19ece25f040bbbcbd72/ghc >--------------------------------------------------------------- commit ee4e1654c31b9c6f6ad9b19ece25f040bbbcbd72 Author: Edward Z. Yang Date: Wed Dec 14 01:28:43 2016 -0800 Support for abi-depends for computing shadowing. Summary: This is a complete fix based off of ed7af26606b3a605a4511065ca1a43b1c0f3b51d for handling shadowing and out-of-order -package-db flags simultaneously. The general strategy is we first put all databases together, overriding packages as necessary. Once this is done, we successfully prune out broken packages, including packages which depend on a package whose ABI differs from the ABI we need. Our check gracefully degrades in the absence of abi-depends, as we only check deps which are recorded in abi-depends. Contains time and Cabal submodule update. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: niteria, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2846 GHC Trac Issues: #12485 >--------------------------------------------------------------- ee4e1654c31b9c6f6ad9b19ece25f040bbbcbd72 compiler/backpack/DriverBkp.hs | 1 + compiler/ghc.cabal.in | 2 +- compiler/main/Packages.hs | 324 ++++++++++++++++++++++------------ ghc/ghc-bin.cabal.in | 2 +- libraries/Cabal | 2 +- libraries/ghc-boot/GHC/PackageDb.hs | 12 +- libraries/hpc | 2 +- libraries/time | 2 +- testsuite/driver/extra_files.py | 1 + testsuite/tests/cabal/Makefile | 41 ++++- testsuite/tests/cabal/T12485/Makefile | 4 +- testsuite/tests/cabal/T12485/all.T | 3 +- testsuite/tests/cabal/T12485a.stdout | 3 + testsuite/tests/cabal/T1750.stderr | 2 +- testsuite/tests/cabal/all.T | 7 + testsuite/tests/cabal/shadow1.pkg | 1 + testsuite/tests/cabal/shadow2.pkg | 2 + testsuite/tests/cabal/shadow3.pkg | 1 + testsuite/tests/perf/haddock/all.T | 3 +- utils/ghc-cabal/Main.hs | 2 +- utils/ghc-pkg/Main.hs | 1 + 21 files changed, 282 insertions(+), 136 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ee4e1654c31b9c6f6ad9b19ece25f040bbbcbd72 From git at git.haskell.org Wed Dec 21 22:49:32 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 22:49:32 +0000 (UTC) Subject: [commit: ghc] master: Notes on parsing lists in Parser.y (46f7f31) Message-ID: <20161221224932.956063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/46f7f31f3d81fce0790fed25d26e2fc6ac577378/ghc >--------------------------------------------------------------- commit 46f7f31f3d81fce0790fed25d26e2fc6ac577378 Author: Edward Z. Yang Date: Tue Dec 20 23:38:20 2016 -0800 Notes on parsing lists in Parser.y Summary: Maybe everyone knows this but I think it is worth mentioning Signed-off-by: Edward Z. Yang Test Plan: none Reviewers: bgamari, austin Subscribers: thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2890 >--------------------------------------------------------------- 46f7f31f3d81fce0790fed25d26e2fc6ac577378 compiler/parser/Parser.y | 44 ++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 44 insertions(+) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 112c4a9..befd52f 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -316,6 +316,48 @@ correctly, see the README in (REPO)/utils/check-api-annotations for details on how to set up a test using the check-api-annotations utility, and interpret the output it generates. +Note [Parsing lists] +--------------------- +You might be wondering why we spend so much effort encoding our lists this +way: + +importdecls + : importdecls ';' importdecl + | importdecls ';' + | importdecl + | {- empty -} + +This might seem like an awfully roundabout way to declare a list; plus, to add +insult to injury you have to reverse the results at the end. The answer is that +left recursion prevents us from running out of stack space when parsing long +sequences. See: https://www.haskell.org/happy/doc/html/sec-sequences.html for +more guidance. + +By adding/removing branches, you can affect what lists are accepted. Here +are the most common patterns, rewritten as regular expressions for clarity: + + -- Equivalent to: ';'* (x ';'+)* x? (can be empty, permits leading/trailing semis) + xs : xs ';' x + | xs ';' + | x + | {- empty -} + + -- Equivalent to x (';' x)* ';'* (non-empty, permits trailing semis) + xs : xs ';' x + | xs ';' + | x + + -- Equivalent to ';'* alts (';' alts)* ';'* (non-empty, permits leading/trailing semis) + alts : alts1 + | ';' alts + alts1 : alts1 ';' alt + | alts1 ';' + | alt + + -- Equivalent to x (',' x)+ (non-empty, no trailing semis) + xs : x + | x ',' xs + -- ----------------------------------------------------------------------------- -} @@ -665,6 +707,8 @@ body2 :: { ([AddAnn] :(fst $2), snd $2) } | missing_module_keyword top close { ([],snd $2) } + + top :: { ([AddAnn] ,([LImportDecl RdrName], [LHsDecl RdrName])) } : importdecls { (fst $1 From git at git.haskell.org Wed Dec 21 22:49:35 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Dec 2016 22:49:35 +0000 (UTC) Subject: [commit: ghc] master: Update ghc-cabal command line usage text. (99db12f) Message-ID: <20161221224935.502E93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/99db12f54fa5d4dcf264f00c6f97d08d33b587d0/ghc >--------------------------------------------------------------- commit 99db12f54fa5d4dcf264f00c6f97d08d33b587d0 Author: Edward Z. Yang Date: Tue Dec 20 22:09:16 2016 -0800 Update ghc-cabal command line usage text. Summary: Old usage text was horribly out-of-date. Now updated! Signed-off-by: Edward Z. Yang Test Plan: none Reviewers: bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2889 >--------------------------------------------------------------- 99db12f54fa5d4dcf264f00c6f97d08d33b587d0 utils/ghc-cabal/Main.hs | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index 12699a7..608517e 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -66,9 +66,13 @@ main = do hSetBuffering stdout LineBuffering syntax_error :: [String] syntax_error = - ["syntax: ghc-cabal configure -- ...", - " ghc-cabal install ...", - " ghc-cabal hscolour ..."] + ["syntax: ghc-cabal configure ...", + " ghc-cabal copy ...", + " ghc-cabal register ...", + " ghc-cabal hscolour ...", + " ghc-cabal check ", + " ghc-cabal sdist ", + " ghc-cabal --version"] die :: [String] -> IO a die errs = do mapM_ (hPutStrLn stderr) errs From git at git.haskell.org Thu Dec 22 01:37:46 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Dec 2016 01:37:46 +0000 (UTC) Subject: [commit: ghc] master: Fix another forward reference to a Note (41ade95) Message-ID: <20161222013746.060203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/41ade95c068e77b916ff17865515eadb353a2358/ghc >--------------------------------------------------------------- commit 41ade95c068e77b916ff17865515eadb353a2358 Author: Ryan Scott Date: Wed Dec 21 20:35:33 2016 -0500 Fix another forward reference to a Note A continuation of ccc918cdc8b2d147c4dbc29bfc87c058862a97cd. [ci skip] >--------------------------------------------------------------- 41ade95c068e77b916ff17865515eadb353a2358 compiler/deSugar/DsMeta.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs index 1c33829..9a76c81 100644 --- a/compiler/deSugar/DsMeta.hs +++ b/compiler/deSugar/DsMeta.hs @@ -724,8 +724,8 @@ rep_ty_sig mk_sig loc sig_ty nm rep_patsyn_ty_sig :: SrcSpan -> LHsSigType Name -> Located Name -> DsM (SrcSpan, Core TH.DecQ) --- represents a pattern synonym type signature; see NOTE [Pattern --- synonym signatures and Template Haskell] +-- represents a pattern synonym type signature; +-- see Note [Pattern synonym type signatures and Template Haskell] in Convert rep_patsyn_ty_sig loc sig_ty nm = do { nm1 <- lookupLOcc nm ; ty1 <- repHsPatSynSigType sig_ty From git at git.haskell.org Thu Dec 22 13:59:54 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Dec 2016 13:59:54 +0000 (UTC) Subject: [commit: ghc] master: Revert "Suppress duplicate .T files" (b7a6e62) Message-ID: <20161222135954.BE5203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b7a6e6220289289796d03cf1738e6c77daf6c181/ghc >--------------------------------------------------------------- commit b7a6e6220289289796d03cf1738e6c77daf6c181 Author: Gabor Greif Date: Thu Dec 22 14:57:27 2016 +0100 Revert "Suppress duplicate .T files" This reverts commit 9a29b65bda8aed4c5fdbff25866ddf2dd1583210. It turns out that while not harmful, that commit is unnecessary, and a `make clean` resolved it. See: https://phabricator.haskell.org/rGHC9a29b65bda8aed4c5fdbff25866ddf2dd1583210 >--------------------------------------------------------------- b7a6e6220289289796d03cf1738e6c77daf6c181 testsuite/driver/runtests.py | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index a30763c..28b393a 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -255,7 +255,7 @@ print('Timeout is ' + str(config.timeout)) if config.rootdirs == []: config.rootdirs = ['.'] -t_files = set(findTFiles(config.rootdirs)) +t_files = list(findTFiles(config.rootdirs)) print('Found', len(t_files), '.T files...') From git at git.haskell.org Fri Dec 23 11:56:20 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 11:56:20 +0000 (UTC) Subject: [commit: ghc] master: Allow timeout to kill entire process tree. (efc4a16) Message-ID: <20161223115620.1064A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/efc4a1661f0fc1004a4b7b0914f3d3a08c2e791a/ghc >--------------------------------------------------------------- commit efc4a1661f0fc1004a4b7b0914f3d3a08c2e791a Author: Tamar Christina Date: Fri Dec 23 00:56:34 2016 +0000 Allow timeout to kill entire process tree. Summary: we spawn the child processes with handle inheritance on. So they inherit the std handles. The problem is that the job handle gets inherited too. So the `JOB_OBJECT_LIMIT_KILL_ON_JOB_CLOSE` doesn't get used since there are open handles to the job in the children. We then terminate the top level process which is `sh` but leaves the children around. This explicitly disallows the inheritance of the job and events handle. Test Plan: ./validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie, #ghc_windows_task_force Differential Revision: https://phabricator.haskell.org/D2895 GHC Trac Issues: #13004 >--------------------------------------------------------------- efc4a1661f0fc1004a4b7b0914f3d3a08c2e791a testsuite/timeout/WinCBindings.hsc | 8 +++++++- testsuite/timeout/timeout.hs | 8 ++++++++ 2 files changed, 15 insertions(+), 1 deletion(-) diff --git a/testsuite/timeout/WinCBindings.hsc b/testsuite/timeout/WinCBindings.hsc index 36ba01e..0c4ff3f 100644 --- a/testsuite/timeout/WinCBindings.hsc +++ b/testsuite/timeout/WinCBindings.hsc @@ -293,6 +293,9 @@ cWAIT_TIMEOUT = #const WAIT_TIMEOUT cCREATE_SUSPENDED :: DWORD cCREATE_SUSPENDED = #const CREATE_SUSPENDED +cHANDLE_FLAG_INHERIT :: DWORD +cHANDLE_FLAG_INHERIT = #const HANDLE_FLAG_INHERIT + foreign import WINDOWS_CCONV unsafe "windows.h GetExitCodeProcess" getExitCodeProcess :: HANDLE -> LPDWORD -> IO BOOL @@ -325,13 +328,16 @@ foreign import WINDOWS_CCONV unsafe "windows.h CreateIoCompletionPort" foreign import WINDOWS_CCONV unsafe "windows.h GetQueuedCompletionStatus" getQueuedCompletionStatus :: HANDLE -> LPDWORD -> PULONG_PTR -> Ptr LPOVERLAPPED -> DWORD -> IO BOOL +foreign import WINDOWS_CCONV unsafe "windows.h SetHandleInformation" + setHandleInformation :: HANDLE -> DWORD -> DWORD -> IO BOOL + setJobParameters :: HANDLE -> IO BOOL setJobParameters hJob = alloca $ \p_jeli -> do let jeliSize = sizeOf (undefined :: JOBOBJECT_EXTENDED_LIMIT_INFORMATION) _ <- memset p_jeli 0 $ fromIntegral jeliSize -- Configure all child processes associated with the job to terminate when the - -- Last process in the job terminates. This prevent half dead processes and that + -- last handle to the job is closed. This prevent half dead processes and that -- hanging ghc-iserv.exe process that happens when you interrupt the testsuite. (#poke JOBOBJECT_EXTENDED_LIMIT_INFORMATION, BasicLimitInformation.LimitFlags) p_jeli cJOB_OBJECT_LIMIT_KILL_ON_JOB_CLOSE diff --git a/testsuite/timeout/timeout.hs b/testsuite/timeout/timeout.hs index cf6c448..4e97c5c 100644 --- a/testsuite/timeout/timeout.hs +++ b/testsuite/timeout/timeout.hs @@ -109,6 +109,14 @@ run secs cmd = ioPort <- createCompletionPort job when (ioPort == nullPtr) $ errorWin "createCompletionPort, cannot continue." + -- We're explicitly turning off handle inheritance to prevent misc handles + -- from being inherited by the child. Notable we don't want the I/O CP and + -- Job handles to be inherited. So we mark them as non-inheritable. + setHandleInformation job cHANDLE_FLAG_INHERIT 0 + setHandleInformation job cHANDLE_FLAG_INHERIT 0 + + -- Now create the process suspended so we can add it to the job and then resume. + -- This is so we don't miss any events on the receiving end of the I/O port. let creationflags = cCREATE_SUSPENDED b <- createProcessW nullPtr cmd'' nullPtr nullPtr True creationflags From git at git.haskell.org Fri Dec 23 12:34:53 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 12:34:53 +0000 (UTC) Subject: [commit: ghc] master: Float unboxed expressions by boxing (432f952) Message-ID: <20161223123453.4619C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/432f952ef64641be9f32152a0fbf2b8496d8fe9c/ghc >--------------------------------------------------------------- commit 432f952ef64641be9f32152a0fbf2b8496d8fe9c Author: Simon Peyton Jones Date: Fri Dec 9 00:04:00 2016 +0000 Float unboxed expressions by boxing This patch makes GHC's floating more robust, by allowing it to float unboxed expressions of at least some common types. See Note [Floating MFEs of unlifted type] in SetLevels. This was all provoked by Trac #12603 In working this through I also made a number of other corner-case changes in SetLevels: * Previously we inconsistently use exprIsBottom (which checks for bottom) instead of exprBotStrictness_maybe (which checks for bottoming functions). As well as being inconsistent it was simply less good. See Note [Bottoming floats] * I fixed a case where were were unprofitably floating an expression because we thought it escaped a value lambda (see Note [Escaping a value lambda]). The relevant code is float_me = (dest_lvl `ltMajLvl` (le_ctxt_lvl env) && not float_is_lam) -- NEW * I made lvlFloatRhs work properly in the case where abs_vars is non-empty. It wasn't wrong before, but it did some stupid extra floating. >--------------------------------------------------------------- 432f952ef64641be9f32152a0fbf2b8496d8fe9c compiler/prelude/TysPrim.hs | 12 +- compiler/prelude/TysWiredIn.hs | 28 ++ compiler/simplCore/SetLevels.hs | 297 +++++++++++++-------- testsuite/tests/simplCore/should_compile/Makefile | 4 + testsuite/tests/simplCore/should_compile/T12603.hs | 45 ++++ .../tests/simplCore/should_compile/T12603.stdout | 1 + testsuite/tests/simplCore/should_compile/all.T | 5 + 7 files changed, 274 insertions(+), 118 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 432f952ef64641be9f32152a0fbf2b8496d8fe9c From git at git.haskell.org Fri Dec 23 12:34:55 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 12:34:55 +0000 (UTC) Subject: [commit: ghc] master: Ensure that even bottoming functions have an unfolding (11306d6) Message-ID: <20161223123455.F13FD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/11306d62250bcb8c40b1feb511ab90006dcd01d5/ghc >--------------------------------------------------------------- commit 11306d62250bcb8c40b1feb511ab90006dcd01d5 Author: Simon Peyton Jones Date: Fri Dec 23 10:06:03 2016 +0000 Ensure that even bottoming functions have an unfolding The payload of this change is to ensure that a bottoming function still has an unfolding, just one with an UnfoldingGuidance of UnfoldNever. Previously it was getting an unfolding of NoUnfolding. I don't think that was really /wrong/, but it was inconsistent with the general principle of giving everthing an unfoding if we know it. And it seems tideier this way. >--------------------------------------------------------------- 11306d62250bcb8c40b1feb511ab90006dcd01d5 compiler/coreSyn/CoreUnfold.hs | 46 ++++++++++++++++++++++++------------------ 1 file changed, 26 insertions(+), 20 deletions(-) diff --git a/compiler/coreSyn/CoreUnfold.hs b/compiler/coreSyn/CoreUnfold.hs index bab798a..f23c662 100644 --- a/compiler/coreSyn/CoreUnfold.hs +++ b/compiler/coreSyn/CoreUnfold.hs @@ -46,7 +46,7 @@ import CoreSyn import PprCore () -- Instances import OccurAnal ( occurAnalyseExpr ) import CoreSubst hiding( substTy ) -import CoreArity ( manifestArity, exprBotStrictness_maybe ) +import CoreArity ( manifestArity ) import CoreUtils import Id import DataCon @@ -63,7 +63,6 @@ import Outputable import ForeignCall import qualified Data.ByteString as BS -import Data.Maybe {- ************************************************************************ @@ -74,12 +73,13 @@ import Data.Maybe -} mkTopUnfolding :: DynFlags -> Bool -> CoreExpr -> Unfolding -mkTopUnfolding dflags = mkUnfolding dflags InlineRhs True {- Top level -} +mkTopUnfolding dflags is_bottoming rhs + = mkUnfolding dflags InlineRhs True is_bottoming rhs mkImplicitUnfolding :: DynFlags -> CoreExpr -> Unfolding -- For implicit Ids, do a tiny bit of optimising first mkImplicitUnfolding dflags expr - = mkTopUnfolding dflags False (simpleOptExpr expr) + = mkTopUnfolding dflags False (simpleOptExpr expr) -- Note [Top-level flag on inline rules] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -88,7 +88,8 @@ mkImplicitUnfolding dflags expr -- Simplify.simplUnfolding. mkSimpleUnfolding :: DynFlags -> CoreExpr -> Unfolding -mkSimpleUnfolding dflags = mkUnfolding dflags InlineRhs False False +mkSimpleUnfolding dflags rhs + = mkUnfolding dflags InlineRhs False False rhs mkDFunUnfolding :: [Var] -> DataCon -> [CoreExpr] -> Unfolding mkDFunUnfolding bndrs con ops @@ -120,7 +121,7 @@ mkWorkerUnfolding dflags work_fn = mkCoreUnfolding src top_lvl new_tmpl guidance where new_tmpl = simpleOptExpr (work_fn tmpl) - guidance = calcUnfoldingGuidance dflags new_tmpl + guidance = calcUnfoldingGuidance dflags False new_tmpl mkWorkerUnfolding _ _ _ = noUnfolding @@ -142,10 +143,9 @@ mkInlineUnfolding mb_arity expr mkInlinableUnfolding :: DynFlags -> CoreExpr -> Unfolding mkInlinableUnfolding dflags expr - = mkUnfolding dflags InlineStable True is_bot expr' + = mkUnfolding dflags InlineStable False False expr' where expr' = simpleOptExpr expr - is_bot = isJust (exprBotStrictness_maybe expr') specUnfolding :: [Var] -> (CoreExpr -> CoreExpr) -> Arity -> Unfolding -> Unfolding -- See Note [Specialising unfoldings] @@ -231,26 +231,27 @@ mkCoreUnfolding src top_lvl expr guidance uf_expandable = exprIsExpandable expr, uf_guidance = guidance } -mkUnfolding :: DynFlags -> UnfoldingSource -> Bool -> Bool -> CoreExpr +mkUnfolding :: DynFlags -> UnfoldingSource + -> Bool -- Is top-level + -> Bool -- Definitely a bottoming binding + -- (only relevant for top-level bindings) + -> CoreExpr -> Unfolding -- Calculates unfolding guidance -- Occurrence-analyses the expression before capturing it -mkUnfolding dflags src top_lvl is_bottoming expr - | top_lvl && is_bottoming - , not (exprIsTrivial expr) - = NoUnfolding -- See Note [Do not inline top-level bottoming functions] - | otherwise +mkUnfolding dflags src is_top_lvl is_bottoming expr = CoreUnfolding { uf_tmpl = occurAnalyseExpr expr, -- See Note [Occurrrence analysis of unfoldings] uf_src = src, - uf_is_top = top_lvl, + uf_is_top = is_top_lvl, uf_is_value = exprIsHNF expr, uf_is_conlike = exprIsConLike expr, uf_expandable = exprIsExpandable expr, uf_is_work_free = exprIsWorkFree expr, uf_guidance = guidance } where - guidance = calcUnfoldingGuidance dflags expr + is_top_bottoming = is_top_lvl && is_bottoming + guidance = calcUnfoldingGuidance dflags is_top_bottoming expr -- NB: *not* (calcUnfoldingGuidance (occurAnalyseExpr expr))! -- See Note [Calculate unfolding guidance on the non-occ-anal'd expression] @@ -328,12 +329,13 @@ inlineBoringOk e calcUnfoldingGuidance :: DynFlags - -> CoreExpr -- Expression to look at + -> Bool -- Definitely a top-level, bottoming binding + -> CoreExpr -- Expression to look at -> UnfoldingGuidance -calcUnfoldingGuidance dflags (Tick t expr) +calcUnfoldingGuidance dflags is_top_bottoming (Tick t expr) | not (tickishIsCode t) -- non-code ticks don't matter for unfolding - = calcUnfoldingGuidance dflags expr -calcUnfoldingGuidance dflags expr + = calcUnfoldingGuidance dflags is_top_bottoming expr +calcUnfoldingGuidance dflags is_top_bottoming expr = case sizeExpr dflags bOMB_OUT_SIZE val_bndrs body of TooBig -> UnfNever SizeIs size cased_bndrs scrut_discount @@ -341,6 +343,10 @@ calcUnfoldingGuidance dflags expr -> UnfWhen { ug_unsat_ok = unSaturatedOk , ug_boring_ok = boringCxtOk , ug_arity = n_val_bndrs } -- Note [INLINE for small functions] + + | is_top_bottoming + -> UnfNever -- See Note [Do not inline top-level bottoming functions] + | otherwise -> UnfIfGoodArgs { ug_args = map (mk_discount cased_bndrs) val_bndrs , ug_size = size From git at git.haskell.org Fri Dec 23 12:34:58 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 12:34:58 +0000 (UTC) Subject: [commit: ghc] master: White space only (ea8f91d) Message-ID: <20161223123458.B70593A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ea8f91d3915fc41f0eeabef2c773e8250b6bccb0/ghc >--------------------------------------------------------------- commit ea8f91d3915fc41f0eeabef2c773e8250b6bccb0 Author: Simon Peyton Jones Date: Fri Dec 23 10:04:02 2016 +0000 White space only >--------------------------------------------------------------- ea8f91d3915fc41f0eeabef2c773e8250b6bccb0 compiler/main/TidyPgm.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/compiler/main/TidyPgm.hs b/compiler/main/TidyPgm.hs index c4057fc..52137a4 100644 --- a/compiler/main/TidyPgm.hs +++ b/compiler/main/TidyPgm.hs @@ -1255,10 +1255,10 @@ tidyTopIdInfo dflags rhs_tidy_env name orig_rhs tidy_rhs idinfo show_unfold caf_ sig = strictnessInfo idinfo final_sig | not $ isTopSig sig - = WARN( _bottom_hidden sig , ppr name ) sig - -- try a cheap-and-cheerful bottom analyser - | Just (_, nsig) <- mb_bot_str = nsig - | otherwise = sig + = WARN( _bottom_hidden sig , ppr name ) sig + -- try a cheap-and-cheerful bottom analyser + | Just (_, nsig) <- mb_bot_str = nsig + | otherwise = sig _bottom_hidden id_sig = case mb_bot_str of Nothing -> False From git at git.haskell.org Fri Dec 23 12:35:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 12:35:01 +0000 (UTC) Subject: [commit: ghc] master: Alpha-renaming and white space only (7a13f1f) Message-ID: <20161223123501.84FA33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7a13f1f79b690a173a3df0db6434e89a91da32e5/ghc >--------------------------------------------------------------- commit 7a13f1f79b690a173a3df0db6434e89a91da32e5 Author: Simon Peyton Jones Date: Thu Dec 22 13:49:35 2016 +0000 Alpha-renaming and white space only >--------------------------------------------------------------- 7a13f1f79b690a173a3df0db6434e89a91da32e5 compiler/simplCore/Simplify.hs | 21 +++++++++++---------- 1 file changed, 11 insertions(+), 10 deletions(-) diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index 4f65b2b..18abb2c 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -2894,9 +2894,9 @@ simplLetUnfolding env top_lvl id new_rhs unf | isStableUnfolding unf = simplUnfolding env top_lvl id unf | otherwise - = bottoming `seq` -- See Note [Force bottoming field] + = is_bottoming `seq` -- See Note [Force bottoming field] do { dflags <- getDynFlags - ; return (mkUnfolding dflags InlineRhs (isTopLevel top_lvl) bottoming new_rhs) } + ; return (mkUnfolding dflags InlineRhs is_top_lvl is_bottoming new_rhs) } -- We make an unfolding *even for loop-breakers*. -- Reason: (a) It might be useful to know that they are WHNF -- (b) In TidyPgm we currently assume that, if we want to @@ -2904,7 +2904,8 @@ simplLetUnfolding env top_lvl id new_rhs unf -- to expose. (We could instead use the RHS, but currently -- we don't.) The simple thing is always to have one. where - bottoming = isBottomingId id + is_top_lvl = isTopLevel top_lvl + is_bottoming = isBottomingId id simplUnfolding :: SimplEnv-> TopLevelFlag -> InId -> Unfolding -> SimplM Unfolding -- Note [Setting the new unfolding] @@ -2935,20 +2936,20 @@ simplUnfolding env top_lvl id unf -- See Note [Top-level flag on inline rules] in CoreUnfold _other -- Happens for INLINABLE things - -> bottoming `seq` -- See Note [Force bottoming field] + -> is_bottoming `seq` -- See Note [Force bottoming field] do { dflags <- getDynFlags - ; return (mkUnfolding dflags src is_top_lvl bottoming expr') } } + ; return (mkUnfolding dflags src is_top_lvl is_bottoming expr') } } -- If the guidance is UnfIfGoodArgs, this is an INLINABLE -- unfolding, and we need to make sure the guidance is kept up -- to date with respect to any changes in the unfolding. | otherwise -> return noUnfolding -- Discard unstable unfoldings where - bottoming = isBottomingId id - is_top_lvl = isTopLevel top_lvl - act = idInlineActivation id - rule_env = updMode (updModeForStableUnfoldings act) env - -- See Note [Simplifying inside stable unfoldings] in SimplUtils + is_top_lvl = isTopLevel top_lvl + is_bottoming = isBottomingId id + act = idInlineActivation id + rule_env = updMode (updModeForStableUnfoldings act) env + -- See Note [Simplifying inside stable unfoldings] in SimplUtils {- Note [Force bottoming field] From git at git.haskell.org Fri Dec 23 12:35:04 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 12:35:04 +0000 (UTC) Subject: [commit: ghc] master: Comments only (9a4af2c) Message-ID: <20161223123504.4512C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9a4af2c451baa685492ed576447c3ce2e335427d/ghc >--------------------------------------------------------------- commit 9a4af2c451baa685492ed576447c3ce2e335427d Author: Simon Peyton Jones Date: Fri Dec 23 10:04:23 2016 +0000 Comments only >--------------------------------------------------------------- 9a4af2c451baa685492ed576447c3ce2e335427d compiler/simplCore/SimplCore.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index ca869dc..8e9a9c6 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -344,6 +344,8 @@ getCoreToDo dflags -- Final run of the demand_analyser, ensures that one-shot thunks are -- really really one-shot thunks. Only needed if the demand analyser -- has run at all. See Note [Final Demand Analyser run] in DmdAnal + -- It is EXTREMELY IMPORTANT to run this pass, otherwise execution + -- can become /exponentially/ more expensive. See Trac #11731, #12996. runWhen (strictness || late_dmd_anal) CoreDoStrictness, maybe_rule_check (Phase 0) From git at git.haskell.org Fri Dec 23 12:35:07 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 12:35:07 +0000 (UTC) Subject: [commit: ghc] master: Fix a bug in ABot handling in CoreArity (f06b71a) Message-ID: <20161223123507.BE7DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f06b71ae2e76ec81a618bc8bb0409b3fc6a7ebbe/ghc >--------------------------------------------------------------- commit f06b71ae2e76ec81a618bc8bb0409b3fc6a7ebbe Author: Simon Peyton Jones Date: Fri Dec 23 09:33:07 2016 +0000 Fix a bug in ABot handling in CoreArity See Note [ABot branches: use max] in CoreArity. I stumbled on this when investigating something else, and opened Trac #13031 to track it. It's very hard to tickle the bug, which is why it has lurked so long, but the test stranal/should_compile/T13031 does so Oddly, the testsuite framework doesn't actually run the test; I have no idea why. >--------------------------------------------------------------- f06b71ae2e76ec81a618bc8bb0409b3fc6a7ebbe compiler/coreSyn/CoreArity.hs | 13 ++++++++++--- testsuite/tests/stranal/should_compile/Makefile | 4 ++++ testsuite/tests/stranal/should_compile/T13031.hs | 11 +++++++++++ testsuite/tests/stranal/should_compile/T13031.stdout | 4 ++++ testsuite/tests/stranal/should_compile/all.T | 3 +++ 5 files changed, 32 insertions(+), 3 deletions(-) diff --git a/compiler/coreSyn/CoreArity.hs b/compiler/coreSyn/CoreArity.hs index f5e7673..e6b1f11 100644 --- a/compiler/coreSyn/CoreArity.hs +++ b/compiler/coreSyn/CoreArity.hs @@ -654,8 +654,7 @@ arityApp (ATop []) _ = ATop [] arityApp (ATop (_:as)) cheap = floatIn cheap (ATop as) andArityType :: ArityType -> ArityType -> ArityType -- Used for branches of a 'case' -andArityType (ABot n1) (ABot n2) - = ABot (n1 `min` n2) +andArityType (ABot n1) (ABot n2) = ABot (n1 `max` n2) -- Note [ABot branches: use max] andArityType (ATop as) (ABot _) = ATop as andArityType (ABot _) (ATop bs) = ATop bs andArityType (ATop as) (ATop bs) = ATop (as `combine` bs) @@ -664,7 +663,15 @@ andArityType (ATop as) (ATop bs) = ATop (as `combine` bs) combine [] bs = takeWhile isOneShotInfo bs combine as [] = takeWhile isOneShotInfo as -{- +{- Note [ABot branches: use max] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider case x of + True -> \x. error "urk" + False -> \xy. error "urk2" + +Remember: ABot n means "if you apply to n args, it'll definitely diverge". +So we need (ABot 2) for the whole thing, the /max/ of the ABot arities. + Note [Combining case branches] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider diff --git a/testsuite/tests/stranal/should_compile/Makefile b/testsuite/tests/stranal/should_compile/Makefile index 9101fbd..16d1f2f 100644 --- a/testsuite/tests/stranal/should_compile/Makefile +++ b/testsuite/tests/stranal/should_compile/Makefile @@ -1,3 +1,7 @@ TOP=../../.. include $(TOP)/mk/boilerplate.mk include $(TOP)/mk/test.mk + +T13031: + echo hello + '$(TEST_HC)' $(TEST_HC_OPTS) -c -fforce-recomp T13031.hs -ddump-simpl | grep 'Arity=' diff --git a/testsuite/tests/stranal/should_compile/T13031.hs b/testsuite/tests/stranal/should_compile/T13031.hs new file mode 100644 index 0000000..d5fe761 --- /dev/null +++ b/testsuite/tests/stranal/should_compile/T13031.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE MagicHash #-} + +module Foo( f ) where +import GHC.Prim + +f True = raise# True +f False = \p q -> raise# False + + + + diff --git a/testsuite/tests/stranal/should_compile/T13031.stdout b/testsuite/tests/stranal/should_compile/T13031.stdout new file mode 100644 index 0000000..b6b9f61 --- /dev/null +++ b/testsuite/tests/stranal/should_compile/T13031.stdout @@ -0,0 +1,4 @@ +echo hello +hello +'/5playpen/simonpj/HEAD-4/inplace/test spaces/ghc-stage2' -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -dno-debug-output -c -fforce-recomp T13031.hs -ddump-simpl | grep 'Arity=' +[GblId, Arity=1, Caf=NoCafRefs] diff --git a/testsuite/tests/stranal/should_compile/all.T b/testsuite/tests/stranal/should_compile/all.T index 0f57c3b..6cd9da4 100644 --- a/testsuite/tests/stranal/should_compile/all.T +++ b/testsuite/tests/stranal/should_compile/all.T @@ -49,4 +49,7 @@ test('T9208', when(compiler_debugged(), expect_broken(9208)), compile, ['']) test('T10694', [ grepCoreString(r'Str=') ], compile, ['-dppr-cols=200 -ddump-simpl']) test('T11770', [ checkCoreString('OneShot') ], compile, ['-ddump-simpl']) +test('T13031', normal, run_command, + ['$MAKE -s --no-print-directory T13031']) + From git at git.haskell.org Fri Dec 23 14:01:49 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 14:01:49 +0000 (UTC) Subject: [commit: ghc] wip/T9291: Add a CSE pass to Stg (#9291) (4065fee) Message-ID: <20161223140149.11D993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9291 Link : http://ghc.haskell.org/trac/ghc/changeset/4065fee08d606b26df6202dc56282d844f99cf5e/ghc >--------------------------------------------------------------- commit 4065fee08d606b26df6202dc56282d844f99cf5e Author: Joachim Breitner Date: Thu Dec 15 10:57:43 2016 -0800 Add a CSE pass to Stg (#9291) This CSE pass only targets data constructor applications. This is probably the best we can do, as function calls and primitive operations might have side-effects. Introduces the flag -fstg-cse, enabled by default with -O. Differential Revision: https://phabricator.haskell.org/D2871 >--------------------------------------------------------------- 4065fee08d606b26df6202dc56282d844f99cf5e compiler/coreSyn/TrieMap.hs | 6 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 3 + compiler/simplStg/SimplStg.hs | 30 +- compiler/simplStg/StgCse.hs | 357 +++++++++++++++++++++ docs/users_guide/using-optimisation.rst | 8 + testsuite/tests/{ado => simplStg}/Makefile | 0 .../should_run}/Makefile | 0 testsuite/tests/simplStg/should_run/T9291.hs | 27 ++ .../should_run/T9291.stdout} | 1 - testsuite/tests/simplStg/should_run/all.T | 12 + 11 files changed, 429 insertions(+), 16 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4065fee08d606b26df6202dc56282d844f99cf5e From git at git.haskell.org Fri Dec 23 14:01:51 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 14:01:51 +0000 (UTC) Subject: [commit: ghc] wip/T9291: More work on STG CSE (42c63be) Message-ID: <20161223140151.C9E0B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9291 Link : http://ghc.haskell.org/trac/ghc/changeset/42c63be6f89dd6bee409b1df6c1f9501640857f1/ghc >--------------------------------------------------------------- commit 42c63be6f89dd6bee409b1df6c1f9501640857f1 Author: Joachim Breitner Date: Thu Dec 22 23:19:32 2016 -0800 More work on STG CSE More notes, use of In… and Out… types, and more careful handling of renaming due to shadowing. (Is shadowing a thing in STG?) >--------------------------------------------------------------- 42c63be6f89dd6bee409b1df6c1f9501640857f1 compiler/basicTypes/Id.hs | 6 + compiler/basicTypes/Var.hs | 19 ++ compiler/coreSyn/CoreSyn.hs | 8 - compiler/simplStg/StgCse.hs | 231 +++++++++++++++-------- compiler/simplStg/UnariseStg.hs | 5 - compiler/stgSyn/StgSyn.hs | 24 ++- testsuite/tests/simplStg/should_run/T9291.hs | 37 +++- testsuite/tests/simplStg/should_run/T9291.stdout | 3 + 8 files changed, 238 insertions(+), 95 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 42c63be6f89dd6bee409b1df6c1f9501640857f1 From git at git.haskell.org Fri Dec 23 14:01:54 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 14:01:54 +0000 (UTC) Subject: [commit: ghc] wip/T9291's head updated: More work on STG CSE (42c63be) Message-ID: <20161223140154.21FC03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T9291' now includes: 0af959b Revert "Do not init record accessors as exported" 87c3b1d fix OpenBSD linkage (wxneeded) 6c816c5 utils/genargs: delete unused tool 8906e7b Reshuffle levity polymorphism checks. 3dbd2b0 Windows: Improve terminal detection mechanism 2d1beb1 rts/win32/IOManager: Fix integer types 343b147 Reexport Language.Haskell.TH.Lib from Language.Haskell.TH 2a02040 Fix bug in previous fix for #5654 90cfa84 Run some tests with -fexternal-interpreter -prof 21dde81 Improve StringBuffer and FastString docs e0fe7c3 Docs: Delete duplicate paragraph in user guide 52ba947 Allow use of the external interpreter in stage1. 25b70a2 Check family instance consistency of hs-boot families later, fixes #11062. 630cfc3 Fix Haddock comment typo. b5d788a Introduce unboxedSum{Data,Type}Name to template-haskell 513eb6a Fix #12998 by removing CTimer 88e8194 T12035j: disable on NOSMP targets 4704d65 T8209: disable on NOSMP targets 7f5be7e T10296a: disable on NOSMP targets d327ebd regalloc_unit_tests: disable on UNREG targets bb74bc7 T8242: disable on NOSMP targets f1dfce1 Revert "Allow use of the external interpreter in stage1." 6263e10 Fix timeout's timeout on Windows c0c1f80 Mark T8089 as unbroken since #7325 is now resolved 27f7925 Allow use of the external interpreter in stage1. 4535fa2 Test Trac #12996 8fdb937 Make CompactionFailed a newtype 574abb7 Rewrite Note [Api annotations] for clarity. 9a29b65 Suppress duplicate .T files 1771da2 Fix typos (not test relevant) f97d489 Test Trac #12968, plus some comments c73a982 Add note for rebindable syntax of [a..b] c66dd05 Move typeSize/coercionSize into TyCoRep d250d49 Add INLINE pragamas on Traversable default methods e07ad4d Don't eta-expand in stable unfoldings 0a18231 Lint DFunUnfoldings 05d233e Move InId/OutId to CoreSyn c48595e Never apply worker/wrapper to DFuns 1a4c04b Fix 'SPECIALISE instance' c469db4 Test Trac #12950 74033c4 Improved perf for T12227 ccc918c Fix a forward reference to a Note 2189239 Disambiguate two Notes with identical names ee4e165 Support for abi-depends for computing shadowing. 99db12f Update ghc-cabal command line usage text. 46f7f31 Notes on parsing lists in Parser.y 41ade95 Fix another forward reference to a Note b7a6e62 Revert "Suppress duplicate .T files" 4065fee Add a CSE pass to Stg (#9291) 42c63be More work on STG CSE From git at git.haskell.org Fri Dec 23 15:02:40 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 15:02:40 +0000 (UTC) Subject: [commit: ghc] master: Tiny refactor in CoreTidy (793ddb6) Message-ID: <20161223150240.ED95F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/793ddb6574dcb62b4b74cd6fa13c77a4117ea76d/ghc >--------------------------------------------------------------- commit 793ddb6574dcb62b4b74cd6fa13c77a4117ea76d Author: Simon Peyton Jones Date: Thu Dec 22 12:20:13 2016 +0000 Tiny refactor in CoreTidy >--------------------------------------------------------------- 793ddb6574dcb62b4b74cd6fa13c77a4117ea76d compiler/coreSyn/CoreTidy.hs | 20 ++++++++++---------- 1 file changed, 10 insertions(+), 10 deletions(-) diff --git a/compiler/coreSyn/CoreTidy.hs b/compiler/coreSyn/CoreTidy.hs index 782e11a..000a8c5 100644 --- a/compiler/coreSyn/CoreTidy.hs +++ b/compiler/coreSyn/CoreTidy.hs @@ -55,30 +55,30 @@ tidyBind env (Rec prs) ------------ Expressions -------------- tidyExpr :: TidyEnv -> CoreExpr -> CoreExpr -tidyExpr env (Var v) = Var (tidyVarOcc env v) -tidyExpr env (Type ty) = Type (tidyType env ty) +tidyExpr env (Var v) = Var (tidyVarOcc env v) +tidyExpr env (Type ty) = Type (tidyType env ty) tidyExpr env (Coercion co) = Coercion (tidyCo env co) -tidyExpr _ (Lit lit) = Lit lit -tidyExpr env (App f a) = App (tidyExpr env f) (tidyExpr env a) -tidyExpr env (Tick t e) = Tick (tidyTickish env t) (tidyExpr env e) -tidyExpr env (Cast e co) = Cast (tidyExpr env e) (tidyCo env co) +tidyExpr _ (Lit lit) = Lit lit +tidyExpr env (App f a) = App (tidyExpr env f) (tidyExpr env a) +tidyExpr env (Tick t e) = Tick (tidyTickish env t) (tidyExpr env e) +tidyExpr env (Cast e co) = Cast (tidyExpr env e) (tidyCo env co) tidyExpr env (Let b e) = tidyBind env b =: \ (env', b') -> Let b' (tidyExpr env' e) tidyExpr env (Case e b ty alts) - = tidyBndr env b =: \ (env', b) -> + = tidyBndr env b =: \ (env', b) -> Case (tidyExpr env e) b (tidyType env ty) - (map (tidyAlt b env') alts) + (map (tidyAlt env') alts) tidyExpr env (Lam b e) = tidyBndr env b =: \ (env', b) -> Lam b (tidyExpr env' e) ------------ Case alternatives -------------- -tidyAlt :: CoreBndr -> TidyEnv -> CoreAlt -> CoreAlt -tidyAlt _case_bndr env (con, vs, rhs) +tidyAlt :: TidyEnv -> CoreAlt -> CoreAlt +tidyAlt env (con, vs, rhs) = tidyBndrs env vs =: \ (env', vs) -> (con, vs, tidyExpr env' rhs) From git at git.haskell.org Fri Dec 23 15:02:44 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 15:02:44 +0000 (UTC) Subject: [commit: ghc] master: Propagate evaluated-ness a bit more faithfully (75e8c30) Message-ID: <20161223150244.0D6813A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/75e8c305a497ec5ad3e5a5d9ff73bbf6f7a8a000/ghc >--------------------------------------------------------------- commit 75e8c305a497ec5ad3e5a5d9ff73bbf6f7a8a000 Author: Simon Peyton Jones Date: Thu Dec 22 12:22:47 2016 +0000 Propagate evaluated-ness a bit more faithfully This was provoked by Trac #13027. The fix in Simplify actually cures the reported bug; see Note [Case binder evaluated-ness] in Simplify. The fix in CoreTidy looks like an omission that I fixed while I was at it. >--------------------------------------------------------------- 75e8c305a497ec5ad3e5a5d9ff73bbf6f7a8a000 compiler/coreSyn/CoreTidy.hs | 2 ++ compiler/simplCore/Simplify.hs | 24 ++++++++++++++--- testsuite/tests/simplCore/should_compile/T13027.hs | 30 ++++++++++++++++++++++ testsuite/tests/simplCore/should_compile/all.T | 1 + 4 files changed, 54 insertions(+), 3 deletions(-) diff --git a/compiler/coreSyn/CoreTidy.hs b/compiler/coreSyn/CoreTidy.hs index 000a8c5..7f82bec 100644 --- a/compiler/coreSyn/CoreTidy.hs +++ b/compiler/coreSyn/CoreTidy.hs @@ -205,6 +205,8 @@ tidyLetBndr rec_tidy_env env@(tidy_env, var_env) (id,rhs) `setUnfoldingInfo` new_unf new_unf | isStableUnfolding old_unf = tidyUnfolding rec_tidy_env old_unf old_unf + | isEvaldUnfolding old_unf = evaldUnfolding + -- See Note [Preserve evaluatedness] | otherwise = noUnfolding old_unf = unfoldingInfo old_info in diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index 18abb2c..e51ef05 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -2065,10 +2065,13 @@ simplAlts env scrut case_bndr alts cont' = do { let env0 = zapFloats env ; (env1, case_bndr1) <- simplBinder env0 case_bndr + ; let case_bndr2 = case_bndr1 `setIdUnfolding` evaldUnfolding + env2 = modifyInScope env1 case_bndr2 + -- See Note [Case-binder evaluated-ness] ; fam_envs <- getFamEnvs - ; (alt_env', scrut', case_bndr') <- improveSeq fam_envs env1 scrut - case_bndr case_bndr1 alts + ; (alt_env', scrut', case_bndr') <- improveSeq fam_envs env2 scrut + case_bndr case_bndr2 alts ; (imposs_deflt_cons, in_alts) <- prepareAlts scrut' case_bndr' alts -- NB: it's possible that the returned in_alts is empty: this is handled @@ -2203,7 +2206,22 @@ zapBndrOccInfo keep_occ_info pat_id | keep_occ_info = pat_id | otherwise = zapIdOccInfo pat_id -{- +{- Note [Case binder evaluated-ness] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +We pin on a (OtherCon []) unfolding to the case-binder of a Case, +even though it'll be over-ridden in every case alternative with a more +informative unfolding. Why? Because suppose a later, less clever, pass +simply replaces all occurrences of the case binder with the binder itself; +then Lint may complain about the let/app invariant. Example + case e of b { DEFAULT -> let v = reallyUnsafePtrEq# b y in .... + ; K -> blah } + +The let/app invariant requires that y is evaluated in the call to +reallyUnsafePtrEq#, which it is. But we still want that to be true if we +propagate binders to occurrences. + +This showed up in Trac #13027. + Note [Add unfolding for scrutinee] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ In general it's unlikely that a variable scrutinee will appear diff --git a/testsuite/tests/simplCore/should_compile/T13027.hs b/testsuite/tests/simplCore/should_compile/T13027.hs new file mode 100644 index 0000000..727dfc5 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T13027.hs @@ -0,0 +1,30 @@ +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE MagicHash #-} +module T13027 (insert) where + +import GHC.Exts (isTrue#, reallyUnsafePtrEquality#) + +data Set a = Bin {-# UNPACK #-} !Size !a !(Set a) !(Set a) + | Tip + +type Size = Int + +insert :: Ord a => a -> Set a -> Set a +insert = go + where + go :: Ord a => a -> Set a -> Set a + go !x Tip = Bin 1 x Tip Tip + go !x t@(Bin sz y l r) = case compare x y of + LT | l' `ptrEq` l -> t + | otherwise -> undefined -- balanceL y l' r + where !l' = go x l + GT | r' `ptrEq` r -> t + | otherwise -> undefined -- balanceR y l r' + where !r' = go x r + EQ | x `ptrEq` y -> t + | otherwise -> Bin sz x l r +{-# INLINABLE insert #-} + +ptrEq :: a -> a -> Bool +ptrEq x y = isTrue# (reallyUnsafePtrEquality# x y) +{-# INLINE ptrEq #-} diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index 6b852fc..c5666c4 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -254,4 +254,5 @@ test('T12603', normal, run_command, ['$MAKE -s --no-print-directory T12603']) +test('T13027', normal, compile, ['']) From git at git.haskell.org Fri Dec 23 15:02:46 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 15:02:46 +0000 (UTC) Subject: [commit: ghc] master: Removed dead code in DsCCall.mk_alt (ee872d3) Message-ID: <20161223150246.D93DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ee872d32e024a65d0d7fdd55515262f5d4aecb24/ghc >--------------------------------------------------------------- commit ee872d32e024a65d0d7fdd55515262f5d4aecb24 Author: Simon Peyton Jones Date: Fri Dec 23 10:43:03 2016 +0000 Removed dead code in DsCCall.mk_alt Fixes Trac #13029 by deleting code and adding comments >--------------------------------------------------------------- ee872d32e024a65d0d7fdd55515262f5d4aecb24 compiler/deSugar/DsCCall.hs | 89 +++++++++++++++++++++------------------------ 1 file changed, 41 insertions(+), 48 deletions(-) diff --git a/compiler/deSugar/DsCCall.hs b/compiler/deSugar/DsCCall.hs index d87d935..d7cba65 100644 --- a/compiler/deSugar/DsCCall.hs +++ b/compiler/deSugar/DsCCall.hs @@ -280,32 +280,16 @@ mk_alt return_result (Nothing, wrap_result) return (ccall_res_ty, the_alt) mk_alt return_result (Just prim_res_ty, wrap_result) - -- The ccall returns a non-() value - | isUnboxedTupleType prim_res_ty= do - let - Just ls = tyConAppArgs_maybe prim_res_ty - arity = 1 + length ls - args_ids@(result_id:as) <- mapM newSysLocalDs ls - state_id <- newSysLocalDs realWorldStatePrimTy - let - the_rhs = return_result (Var state_id) - (wrap_result (Var result_id) : map Var as) - ccall_res_ty = mkTupleTy Unboxed (realWorldStatePrimTy : ls) - the_alt = ( DataAlt (tupleDataCon Unboxed arity) - , (state_id : args_ids) - , the_rhs - ) - return (ccall_res_ty, the_alt) - - | otherwise = do - result_id <- newSysLocalDs prim_res_ty - state_id <- newSysLocalDs realWorldStatePrimTy - let - the_rhs = return_result (Var state_id) + = -- The ccall returns a non-() value + ASSERT2( isPrimitiveType prim_res_ty, ppr prim_res_ty ) + -- True because resultWrapper ensures it is so + do { result_id <- newSysLocalDs prim_res_ty + ; state_id <- newSysLocalDs realWorldStatePrimTy + ; let the_rhs = return_result (Var state_id) [wrap_result (Var result_id)] - ccall_res_ty = mkTupleTy Unboxed [realWorldStatePrimTy, prim_res_ty] - the_alt = (DataAlt (tupleDataCon Unboxed 2), [state_id, result_id], the_rhs) - return (ccall_res_ty, the_alt) + ccall_res_ty = mkTupleTy Unboxed [realWorldStatePrimTy, prim_res_ty] + the_alt = (DataAlt (tupleDataCon Unboxed 2), [state_id, result_id], the_rhs) + ; return (ccall_res_ty, the_alt) } resultWrapper :: Type @@ -314,48 +298,57 @@ resultWrapper :: Type -- resultWrapper deals with the result *value* -- E.g. foreign import foo :: Int -> IO T -- Then resultWrapper deals with marshalling the 'T' part +-- So if resultWrapper ty = (Just ty_rep, marshal) +-- then marshal (e :: ty_rep) :: ty +-- That is, 'marshal' wrape the result returned by the foreign call, +-- of type ty_rep, into the value Haskell expected, of type 'ty' +-- +-- Invariant: ty_rep is always a primitive type +-- i.e. (isPrimitiveType ty_rep) is True + resultWrapper result_ty -- Base case 1: primitive types | isPrimitiveType result_ty = return (Just result_ty, \e -> e) -- Base case 2: the unit type () - | Just (tc,_) <- maybe_tc_app, tc `hasKey` unitTyConKey + | Just (tc,_) <- maybe_tc_app + , tc `hasKey` unitTyConKey = return (Nothing, \_ -> Var unitDataConId) -- Base case 3: the boolean type - | Just (tc,_) <- maybe_tc_app, tc `hasKey` boolTyConKey - = do - dflags <- getDynFlags - return - (Just intPrimTy, \e -> mkWildCase e intPrimTy - boolTy - [(DEFAULT ,[],Var trueDataConId ), - (LitAlt (mkMachInt dflags 0),[],Var falseDataConId)]) + | Just (tc,_) <- maybe_tc_app + , tc `hasKey` boolTyConKey + = do { dflags <- getDynFlags + ; let marshal_bool e + = mkWildCase e intPrimTy boolTy + [ (DEFAULT ,[],Var trueDataConId ) + , (LitAlt (mkMachInt dflags 0),[],Var falseDataConId)] + ; return (Just intPrimTy, marshal_bool) } -- Newtypes | Just (co, rep_ty) <- topNormaliseNewType_maybe result_ty - = do (maybe_ty, wrapper) <- resultWrapper rep_ty - return (maybe_ty, \e -> mkCastDs (wrapper e) (mkSymCo co)) + = do { (maybe_ty, wrapper) <- resultWrapper rep_ty + ; return (maybe_ty, \e -> mkCastDs (wrapper e) (mkSymCo co)) } -- The type might contain foralls (eg. for dummy type arguments, -- referring to 'Ptr a' is legal). | Just (tyvar, rest) <- splitForAllTy_maybe result_ty - = do (maybe_ty, wrapper) <- resultWrapper rest - return (maybe_ty, \e -> Lam tyvar (wrapper e)) + = do { (maybe_ty, wrapper) <- resultWrapper rest + ; return (maybe_ty, \e -> Lam tyvar (wrapper e)) } -- Data types with a single constructor, which has a single arg -- This includes types like Ptr and ForeignPtr - | Just (tycon, tycon_arg_tys, data_con, data_con_arg_tys) <- splitDataProductType_maybe result_ty, - dataConSourceArity data_con == 1 - = do dflags <- getDynFlags - let - (unwrapped_res_ty : _) = data_con_arg_tys - narrow_wrapper = maybeNarrow dflags tycon - (maybe_ty, wrapper) <- resultWrapper unwrapped_res_ty - return - (maybe_ty, \e -> mkApps (Var (dataConWrapId data_con)) - (map Type tycon_arg_tys ++ [wrapper (narrow_wrapper e)])) + | Just (tycon, tycon_arg_tys) <- maybe_tc_app + , Just data_con <- isDataProductTyCon_maybe tycon -- One construtor, no existentials + , [unwrapped_res_ty] <- dataConInstOrigArgTys data_con tycon_arg_tys -- One argument + = do { dflags <- getDynFlags + ; (maybe_ty, wrapper) <- resultWrapper unwrapped_res_ty + ; let narrow_wrapper = maybeNarrow dflags tycon + marshal_con e = Var (dataConWrapId data_con) + `mkTyApps` tycon_arg_tys + `App` wrapper (narrow_wrapper e) + ; return (maybe_ty, marshal_con) } | otherwise = pprPanic "resultWrapper" (ppr result_ty) From git at git.haskell.org Fri Dec 23 15:02:50 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 15:02:50 +0000 (UTC) Subject: [commit: ghc] master: Push coercions in exprIsConApp_maybe (b4c3a66) Message-ID: <20161223150250.5B8F43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b4c3a66872a2b6e64fea9cc1f20ef4c8921ef7b6/ghc >--------------------------------------------------------------- commit b4c3a66872a2b6e64fea9cc1f20ef4c8921ef7b6 Author: Simon Peyton Jones Date: Fri Dec 23 12:59:41 2016 +0000 Push coercions in exprIsConApp_maybe Trac #13025 showed up the fact that exprIsConApp_maybe isn't clever enough: it didn't push coercions through applicatins, and that meant we weren't getting as much superclass selection as we should. It's easy to fix, happily. See Note [Push coercions in exprIsConApp_maybe] >--------------------------------------------------------------- b4c3a66872a2b6e64fea9cc1f20ef4c8921ef7b6 compiler/coreSyn/CoreSubst.hs | 50 +++++++++++++++++++++- testsuite/tests/simplCore/should_compile/Makefile | 6 +++ testsuite/tests/simplCore/should_compile/T13025.hs | 15 +++++++ .../tests/simplCore/should_compile/T13025.stdout | 1 + .../tests/simplCore/should_compile/T13025a.hs | 40 +++++++++++++++++ testsuite/tests/simplCore/should_compile/all.T | 4 ++ 6 files changed, 114 insertions(+), 2 deletions(-) diff --git a/compiler/coreSyn/CoreSubst.hs b/compiler/coreSyn/CoreSubst.hs index e8a8f6e..e4f2f59 100644 --- a/compiler/coreSyn/CoreSubst.hs +++ b/compiler/coreSyn/CoreSubst.hs @@ -1196,6 +1196,18 @@ Just (':', [Char], ['a', unpackCString# "bc"]). We need to be careful about UTF8 strings here. ""# contains a ByteString, so we must parse it back into a FastString to split off the first character. That way we can treat unpackCString# and unpackCStringUtf8# in the same way. + +Note [Push coercions in exprIsConApp_maybe] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +In Trac #13025 I found a case where we had + op (df @t1 @t2) -- op is a ClassOp +where + df = (/\a b. K e1 e2) |> g + +To get this to come out we need to simplify on the fly + ((/\a b. K e1 e2) |> g) @t1 @t2 + +Hence the use of pushCoArgs. -} data ConCont = CC [CoreExpr] Coercion @@ -1209,12 +1221,16 @@ exprIsConApp_maybe (in_scope, id_unf) expr = go (Left in_scope) expr (CC [] (mkRepReflCo (exprType expr))) where go :: Either InScopeSet Subst + -- Left in-scope means "empty substitution" + -- Right subst means "apply this substitution to the CoreExpr" -> CoreExpr -> ConCont -> Maybe (DataCon, [Type], [CoreExpr]) go subst (Tick t expr) cont | not (tickishIsCode t) = go subst expr cont - go subst (Cast expr co1) (CC [] co2) - = go subst expr (CC [] (subst_co subst co1 `mkTransCo` co2)) + go subst (Cast expr co1) (CC args co2) + | Just (args', co1') <- pushCoArgs (subst_co subst co1) args + -- See Note [Push coercions in exprIsConApp_maybe] + = go subst expr (CC args' (co1' `mkTransCo` co2)) go subst (App fun arg) (CC args co) = go subst fun (CC (subst_arg subst arg : args) co) go subst (Lam var body) (CC (arg:args) co) @@ -1268,6 +1284,36 @@ exprIsConApp_maybe (in_scope, id_unf) expr extend (Left in_scope) v e = Right (extendSubst (mkEmptySubst in_scope) v e) extend (Right s) v e = Right (extendSubst s v e) +pushCoArgs :: Coercion -> [CoreArg] -> Maybe ([CoreArg], Coercion) +pushCoArgs co [] = return ([], co) +pushCoArgs co (arg:args) = do { (arg', co1) <- pushCoArg co arg + ; (args', co2) <- pushCoArgs co1 args + ; return (arg':args', co2) } + +pushCoArg :: Coercion -> CoreArg -> Maybe (CoreArg, Coercion) +-- We have (fun |> co) arg, and we want to transform it to +-- (fun arg) |> co +-- This may fail, e.g. if (fun :: N) where N is a newtype +-- C.f. simplCast in Simplify.hs + +pushCoArg co arg + = case arg of + Type ty | isForAllTy tyL + -> ASSERT2( isForAllTy tyR, ppr co $$ ppr ty ) + Just (Type ty, mkInstCo co (mkNomReflCo ty)) + + _ | isFunTy tyL + , [co1, co2] <- decomposeCo 2 co + -- If co :: (tyL1 -> tyL2) ~ (tyR1 -> tyR2) + -- then co1 :: tyL1 ~ tyR1 + -- co2 :: tyL2 ~ tyR2 + -> ASSERT2( isFunTy tyR, ppr co $$ ppr arg ) + Just (mkCast arg (mkSymCo co1), co2) + + _ -> Nothing + where + Pair tyL tyR = coercionKind co + -- See Note [exprIsConApp_maybe on literal strings] dealWithStringLiteral :: Var -> BS.ByteString -> Coercion -> Maybe (DataCon, [Type], [CoreExpr]) diff --git a/testsuite/tests/simplCore/should_compile/Makefile b/testsuite/tests/simplCore/should_compile/Makefile index a5d9a1e..5791daf 100644 --- a/testsuite/tests/simplCore/should_compile/Makefile +++ b/testsuite/tests/simplCore/should_compile/Makefile @@ -166,3 +166,9 @@ T5615: -grep 'quotInt#' T5615.dump-simpl -grep 'remInt#' T5615.dump-simpl grep -c '1999#' T5615.dump-simpl + +T13025: + $(RM) -f T13025.o T13025.hi T13025a.o T13025a.hi + '$(TEST_HC)' $(TEST_HC_OPTS) -c -O T13025a.hs + '$(TEST_HC)' $(TEST_HC_OPTS) -c -O T13025.hs -ddump-simpl | grep HEq_sc | wc + # No lines should match 'HEq_sc' so wc should output zeros diff --git a/testsuite/tests/simplCore/should_compile/T13025.hs b/testsuite/tests/simplCore/should_compile/T13025.hs new file mode 100644 index 0000000..01facb8 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T13025.hs @@ -0,0 +1,15 @@ +{-# LANGUAGE DataKinds #-} +module T13025 where +import T13025a + +type MyRec = Rec '[ '("A",Int), '("B",Int), '("C",Int) ] + +getC :: MyRec -> Int +getC = getField (Proxy::Proxy '("C",Int)) + +doubleC :: MyRec -> MyRec +doubleC r = setC (2 * (getC r)) r + where setC = set . (Field :: Int -> Field '("C",Int)) + +main :: IO () +main = print (getC (Field 1 :& Field 2 :& Field 3 :& Nil :: MyRec)) diff --git a/testsuite/tests/simplCore/should_compile/T13025.stdout b/testsuite/tests/simplCore/should_compile/T13025.stdout new file mode 100644 index 0000000..7d1413f --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T13025.stdout @@ -0,0 +1 @@ + 0 0 0 diff --git a/testsuite/tests/simplCore/should_compile/T13025a.hs b/testsuite/tests/simplCore/should_compile/T13025a.hs new file mode 100644 index 0000000..3f9a4cb --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T13025a.hs @@ -0,0 +1,40 @@ +{-# LANGUAGE ConstraintKinds, DataKinds, FlexibleContexts, + FlexibleInstances, GADTs, MultiParamTypeClasses, + PolyKinds, ScopedTypeVariables, TypeFamilies, + TypeOperators #-} +module T13025a where + +data Nat = Z | S Nat +data Proxy a = Proxy + +data Field :: (k,*) -> * where + Field :: a -> Field '(s,a) + +type family Index r rs :: Nat where + Index r (r ': rs) = 'Z + Index r (s ': rs) = 'S (Index r rs) + +data Rec (rs :: [ (k,*) ]) where + Nil :: Rec '[] + (:&) :: Field r -> Rec rs -> Rec (r ': rs) +infixr 5 :& + +class Index r rs ~ i => HasField r rs i where + get :: proxy r -> Rec rs -> Field r + set :: Field r -> Rec rs -> Rec rs + +instance HasField r (r ': rs) 'Z where + get _ (x :& _) = x + set x (_ :& xs) = x :& xs + +instance (HasField r rs i, Index r (s ': rs) ~ 'S i) + => HasField r (s ': rs) ('S i) where + get p (_ :& xs) = get p xs + set x' (x :& xs) = x :& set x' xs + +type Has r rs = HasField r rs (Index r rs) + +getField :: Has '(s,a) rs => proxy '(s,a) -> Rec rs -> a +getField p = aux . get p + where aux :: Field '(s,a) -> a + aux (Field x) = x diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index c5666c4..e09880f 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -255,4 +255,8 @@ test('T12603', run_command, ['$MAKE -s --no-print-directory T12603']) test('T13027', normal, compile, ['']) +test('T13025', + normal, + run_command, + ['$MAKE -s --no-print-directory T13025']) From git at git.haskell.org Fri Dec 23 21:42:51 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 21:42:51 +0000 (UTC) Subject: [commit: ghc] wip/T9291: Stg CSE: Try handle trivial cases less intrusively (49664e9) Message-ID: <20161223214251.5B48E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9291 Link : http://ghc.haskell.org/trac/ghc/changeset/49664e9699c85e14b569450245de0ad98cfcfd22/ghc >--------------------------------------------------------------- commit 49664e9699c85e14b569450245de0ad98cfcfd22 Author: Joachim Breitner Date: Fri Dec 23 22:42:07 2016 +0100 Stg CSE: Try handle trivial cases less intrusively >--------------------------------------------------------------- 49664e9699c85e14b569450245de0ad98cfcfd22 compiler/simplStg/StgCse.hs | 27 ++++++++++----------------- 1 file changed, 10 insertions(+), 17 deletions(-) diff --git a/compiler/simplStg/StgCse.hs b/compiler/simplStg/StgCse.hs index 8d66420..74c1964 100644 --- a/compiler/simplStg/StgCse.hs +++ b/compiler/simplStg/StgCse.hs @@ -137,11 +137,8 @@ data CseEnv = CseEnv , ce_subst :: IdEnv OutId -- ^ This substitution contains CSE-specific entries. The domain are -- OutIds, so ce_renaming has to be applied first. - -- It has entries for two reasons: - -- x ↦ y, when a let-binding `let x = Con y` is removed because - -- `let y = Con z` is in scope - -- b ↦ s, when `case s of b` (trivial scrutinee!) is encountered - -- see Note [Trivial case scrutinee] + -- It has an entry x ↦ y when a let-binding `let x = Con y` is + -- removed because `let y = Con z` is in scope. -- -- Both substitutions are applied to data constructor arguments -- before these are looked up in the conAppMap. @@ -189,11 +186,7 @@ addDataCon :: OutId -> DataCon -> [OutStgArg] -> CseEnv -> CseEnv addDataCon _ _ [] env = env addDataCon bndr dataCon args env = env { ce_conAppMap = new_env } where - new_env = insertTM (dataCon, args) cse_target (ce_conAppMap env) - cse_target = fromMaybe bndr $ lookupVarEnv (ce_subst env) bndr - -- The binder might be a case binder of a trivial case, - -- in which case we want to use the scrutinee - -- See Note [Trivial case scrutinee] + new_env = insertTM (dataCon, args) bndr (ce_conAppMap env) forgetCse :: CseEnv -> CseEnv forgetCse env = env { ce_conAppMap = emptyTM } @@ -300,10 +293,10 @@ stgCseExpr env (StgCase scrut bndr ty alts) where scrut' = stgCseExpr env scrut (env1, bndr') = substBndr env bndr - env2 | StgApp trivial_scrut [] <- scrut' = addSubst bndr' trivial_scrut env1 - -- See Note [Trivial case scrutinee] - | otherwise = env1 - alts' = map (stgCseAlt env2 bndr') alts + cse_bndr | StgApp trivial_scrut [] <- scrut' = trivial_scrut + -- See Note [Trivial case scrutinee] + | otherwise = bndr' + alts' = map (stgCseAlt env1 cse_bndr) alts -- A constructor application. @@ -407,13 +400,13 @@ order to handle nested reconstruction of constructors as in nested _ = Left True Therefore, we add - Con a ↦ x and b ↦ x -to the ConAppMap and the substitution respectively. + Con a ↦ x +to the ConAppMap respectively. Compare Note [CSE for case expressions] in CSE.hs, which does the same for Core CSE. If we find case foo x as b of { Con a -> … } -we only add +we use Con a ↦ b Note [Free variables of an StgClosure] From git at git.haskell.org Fri Dec 23 22:48:10 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 22:48:10 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Split out Windows allocations numbers for T12234 (8712148) Message-ID: <20161223224810.6EA673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/87121488748c3e7a26fe08a82915ebd42fc49235/ghc >--------------------------------------------------------------- commit 87121488748c3e7a26fe08a82915ebd42fc49235 Author: Ben Gamari Date: Wed Dec 21 13:37:59 2016 -0500 testsuite: Split out Windows allocations numbers for T12234 >--------------------------------------------------------------- 87121488748c3e7a26fe08a82915ebd42fc49235 testsuite/tests/perf/compiler/all.T | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 75e361d..9c50fa8 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -890,7 +890,9 @@ test('T12425', test('T12234', [ only_ways(['optasm']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 72958288, 5), + [(platform('x86_64-unknown-mingw32'), 77949232, 5), + # initial: 77949232 + (wordsize(64), 72958288, 5), # initial: 72958288 ]), ], From git at git.haskell.org Fri Dec 23 22:48:13 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 22:48:13 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Kill extraneous link (f95e669) Message-ID: <20161223224813.333C33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f95e6697250ad641efb167ae3cff65eaa5e96d07/ghc >--------------------------------------------------------------- commit f95e6697250ad641efb167ae3cff65eaa5e96d07 Author: Ben Gamari Date: Thu Dec 22 13:07:23 2016 -0500 users-guide: Kill extraneous link >--------------------------------------------------------------- f95e6697250ad641efb167ae3cff65eaa5e96d07 utils/mkUserGuidePart/Options/Warnings.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/mkUserGuidePart/Options/Warnings.hs b/utils/mkUserGuidePart/Options/Warnings.hs index 0f00b51..f18222e 100644 --- a/utils/mkUserGuidePart/Options/Warnings.hs +++ b/utils/mkUserGuidePart/Options/Warnings.hs @@ -421,7 +421,7 @@ warningsOptions = , flag { flagName = "-Wdeferred-out-of-scope-variables" , flagDescription = "Report warnings when variable out-of-scope errors are "++ - ":ref:`deferred until runtime `. "++ + ":ref:`deferred until runtime. "++ "See :ghc-flag:`-fdefer-out-of-scope-variables`." , flagType = DynamicFlag , flagReverse = "-Wno-deferred-out-of-scope-variables" From git at git.haskell.org Fri Dec 23 22:48:16 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 22:48:16 +0000 (UTC) Subject: [commit: ghc] master: rename: Don't require 'fail' in non-monadic contexts (8f89e76) Message-ID: <20161223224816.AC4883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8f89e76389569b73ce0d7550302641bbea438dfc/ghc >--------------------------------------------------------------- commit 8f89e76389569b73ce0d7550302641bbea438dfc Author: Ben Gamari Date: Thu Dec 22 13:55:30 2016 -0500 rename: Don't require 'fail' in non-monadic contexts Fixes #11216. >--------------------------------------------------------------- 8f89e76389569b73ce0d7550302641bbea438dfc compiler/hsSyn/HsExpr.hs | 12 ++++++++++++ compiler/rename/RnExpr.hs | 13 ++++++++++--- testsuite/tests/rebindable/T11216A.hs | 8 ++++++++ testsuite/tests/rebindable/all.T | 3 ++- 4 files changed, 32 insertions(+), 4 deletions(-) diff --git a/compiler/hsSyn/HsExpr.hs b/compiler/hsSyn/HsExpr.hs index d695d8e..1b6ccdc 100644 --- a/compiler/hsSyn/HsExpr.hs +++ b/compiler/hsSyn/HsExpr.hs @@ -2338,6 +2338,15 @@ isMonadCompExpr (ParStmtCtxt ctxt) = isMonadCompExpr ctxt isMonadCompExpr (TransStmtCtxt ctxt) = isMonadCompExpr ctxt isMonadCompExpr _ = False +-- | Should pattern match failure in a 'HsStmtContext' be desugared using +-- 'MonadFail'? +isMonadFailStmtContext :: HsStmtContext id -> Bool +isMonadFailStmtContext MonadComp = True +isMonadFailStmtContext DoExpr = True +isMonadFailStmtContext MDoExpr = True +isMonadFailStmtContext GhciStmtCtxt = True +isMonadFailStmtContext _ = False + matchSeparator :: HsMatchContext id -> SDoc matchSeparator (FunRhs {}) = text "=" matchSeparator CaseAlt = text "->" @@ -2414,6 +2423,9 @@ pprStmtContext (TransStmtCtxt c) | opt_PprStyle_Debug = sep [text "transformed branch of", pprAStmtContext c] | otherwise = pprStmtContext c +instance (Outputable id, Outputable (NameOrRdrName id)) + => Outputable (HsStmtContext id) where + ppr = pprStmtContext -- Used to generate the string for a *runtime* error message matchContextErrString :: Outputable id diff --git a/compiler/rename/RnExpr.hs b/compiler/rename/RnExpr.hs index 7cafc2b..5427579 100644 --- a/compiler/rename/RnExpr.hs +++ b/compiler/rename/RnExpr.hs @@ -803,9 +803,16 @@ rnStmt ctxt rnBody (L loc (BindStmt pat body _ _ _)) thing_inside ; (bind_op, fvs1) <- lookupStmtName ctxt bindMName ; xMonadFailEnabled <- fmap (xopt LangExt.MonadFailDesugaring) getDynFlags - ; let failFunction | xMonadFailEnabled = failMName - | otherwise = failMName_preMFP - ; (fail_op, fvs2) <- lookupSyntaxName failFunction + ; let getFailFunction + -- For non-monadic contexts (e.g. guard patterns, list + -- comprehensions, etc.) we should not need to fail + | not (isMonadFailStmtContext ctxt) + = return (err, emptyFVs) + | xMonadFailEnabled = lookupSyntaxName failMName + | otherwise = lookupSyntaxName failMName_preMFP + where err = pprPanic "rnStmt: fail function forced" + (text "context:" <+> ppr ctxt) + ; (fail_op, fvs2) <- getFailFunction ; rnPat (StmtCtxt ctxt) pat $ \ pat' -> do { (thing, fvs3) <- thing_inside (collectPatBinders pat') diff --git a/testsuite/tests/rebindable/T11216A.hs b/testsuite/tests/rebindable/T11216A.hs new file mode 100644 index 0000000..4bc06f6 --- /dev/null +++ b/testsuite/tests/rebindable/T11216A.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE RebindableSyntax #-} + +module Bug where + +data Maybe a = Just a | Nothing + +foo :: [Maybe a] -> [a] +foo xs = [ x | Just x <- xs ] diff --git a/testsuite/tests/rebindable/all.T b/testsuite/tests/rebindable/all.T index f1737e9..dd51e2b 100644 --- a/testsuite/tests/rebindable/all.T +++ b/testsuite/tests/rebindable/all.T @@ -31,5 +31,6 @@ test('T4851', normal, compile, ['']) test('T5908', normal, compile, ['']) test('T10112', normal, compile, ['']) -test('T11216', [expect_broken(11216)], compile, ['']) +test('T11216', normal, compile, ['']) +test('T11216A', normal, compile, ['']) test('T12080', normal, compile, ['']) From git at git.haskell.org Fri Dec 23 22:48:19 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 22:48:19 +0000 (UTC) Subject: [commit: ghc] master: Use python3 for linters (46a195f) Message-ID: <20161223224819.69AD43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/46a195f4433876f2c6bafeb35a8ec2ed617da396/ghc >--------------------------------------------------------------- commit 46a195f4433876f2c6bafeb35a8ec2ed617da396 Author: Matthew Pickering Date: Fri Dec 23 14:35:55 2016 -0500 Use python3 for linters We now require python3 for the testsuite so rather than require two versions of python it makes sense to use python3 for the linters as well. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2888 >--------------------------------------------------------------- 46a195f4433876f2c6bafeb35a8ec2ed617da396 .arc-linters/check-binaries.py | 2 +- .arc-linters/check-cpp.py | 2 +- .arc-linters/check-makefiles.py | 2 +- .arclint | 6 +++--- 4 files changed, 6 insertions(+), 6 deletions(-) diff --git a/.arc-linters/check-binaries.py b/.arc-linters/check-binaries.py index 85227ea..017b89b 100755 --- a/.arc-linters/check-binaries.py +++ b/.arc-linters/check-binaries.py @@ -1,4 +1,4 @@ -#!/usr/bin/env python +#!/usr/bin/env python3 # A linter to warn when binary files are added to the repository diff --git a/.arc-linters/check-cpp.py b/.arc-linters/check-cpp.py index f9d0552..7abbc31 100755 --- a/.arc-linters/check-cpp.py +++ b/.arc-linters/check-cpp.py @@ -1,4 +1,4 @@ -#!/usr/bin/env python +#!/usr/bin/env python3 # A linter to warn for ASSERT macros which are separated from their argument # list by a space, which Clang's CPP barfs on diff --git a/.arc-linters/check-makefiles.py b/.arc-linters/check-makefiles.py index 7080954..4778b2d 100644 --- a/.arc-linters/check-makefiles.py +++ b/.arc-linters/check-makefiles.py @@ -1,4 +1,4 @@ -#!/usr/bin/env python +#!/usr/bin/env python3 # Warn for use of `--interactive` inside Makefiles (#11468). # diff --git a/.arclint b/.arclint index 7eaced6..95355e2 100644 --- a/.arclint +++ b/.arclint @@ -71,17 +71,17 @@ }, "check-binaries": { "type": "external-json", - "external-json.script": "python .arc-linters/check-binaries.py" + "external-json.script": "python3 .arc-linters/check-binaries.py" }, "check-makefiles": { "type": "external-json", "include": ["(Makefile$)"], - "external-json.script": "python .arc-linters/check-makefiles.py" + "external-json.script": "python3 .arc-linters/check-makefiles.py" }, "bad-assert-clang-cpp": { "type": "external-json", "include": ["(\\.(l?hs|x|y\\.pp)(\\.in)?$)", "(\\.(c|h)$)"], - "external-json.script": "python .arc-linters/check-cpp.py" + "external-json.script": "python3 .arc-linters/check-cpp.py" } }, From git at git.haskell.org Fri Dec 23 22:48:23 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 22:48:23 +0000 (UTC) Subject: [commit: ghc] master: Add caret diagnostics (158530a) Message-ID: <20161223224823.90E033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/158530a5450b27eb5ae2d75b7895fd1662dde13b/ghc >--------------------------------------------------------------- commit 158530a5450b27eb5ae2d75b7895fd1662dde13b Author: Phil Ruffwind Date: Thu Dec 22 17:06:51 2016 -0500 Add caret diagnostics This is controlled by -f[no-]diagnostics-show-caret. Example of what it looks like: ``` | 42 | x = 1 + () | ^^^^^^ ``` This is appended to each diagnostic message. Test Plan: testsuite/tests/warnings/should_fail/CaretDiagnostics1 testsuite/tests/warnings/should_fail/CaretDiagnostics2 Reviewers: simonpj, austin, bgamari Reviewed By: simonpj, bgamari Subscribers: joehillen, mpickering, Phyx, simonpj, alanz, thomie Differential Revision: https://phabricator.haskell.org/D2718 GHC Trac Issues: #8809 >--------------------------------------------------------------- 158530a5450b27eb5ae2d75b7895fd1662dde13b .arc-linters/check-binaries.py | 4 +- .arc-linters/check-cpp.py | 4 +- compiler/main/DynFlags.hs | 16 +++- compiler/main/ErrUtils.hs | 97 ++++++++++++++++++++-- compiler/main/ErrUtils.hs-boot | 1 + docs/users_guide/using.rst | 6 ++ testsuite/mk/test.mk | 1 + testsuite/tests/ghci/scripts/T9293.stdout | 4 + testsuite/tests/ghci/scripts/ghci024.stdout | 1 + testsuite/tests/ghci/scripts/ghci057.stdout | 4 + .../warnings/should_fail/CaretDiagnostics1.hs | 17 ++++ .../warnings/should_fail/CaretDiagnostics1.stderr | 72 ++++++++++++++++ .../warnings/should_fail/CaretDiagnostics2.hs | 3 + .../warnings/should_fail/CaretDiagnostics2.stderr | 6 ++ testsuite/tests/warnings/should_fail/all.T | 2 + utils/mkUserGuidePart/Options/Verbosity.hs | 4 + 16 files changed, 228 insertions(+), 14 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 158530a5450b27eb5ae2d75b7895fd1662dde13b From git at git.haskell.org Fri Dec 23 22:48:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 22:48:26 +0000 (UTC) Subject: [commit: ghc] master: base: Override Foldable.{toList, length} for NonEmpty (94d2cce) Message-ID: <20161223224826.5BE373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/94d2cce6742235d36efb71cf704acd1327a68481/ghc >--------------------------------------------------------------- commit 94d2cce6742235d36efb71cf704acd1327a68481 Author: Artyom Date: Fri Dec 23 14:36:55 2016 -0500 base: Override Foldable.{toList,length} for NonEmpty Previously the Foldable instance for NonEmpty used default implementations for toList and length. I assume that the existing implementations (i.e. Data.List.NonEmpty.{toList,length}) are better than the default ones, and frankly can't see a good reason why they might be worse – but if they are, instead of this commit we'd have to switch Data.List.NonEmpty.{toList,length} to use Foldable. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: int-index, thomie Differential Revision: https://phabricator.haskell.org/D2882 >--------------------------------------------------------------- 94d2cce6742235d36efb71cf704acd1327a68481 libraries/base/Data/List/NonEmpty.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/libraries/base/Data/List/NonEmpty.hs b/libraries/base/Data/List/NonEmpty.hs index b4da532..c5f6169 100644 --- a/libraries/base/Data/List/NonEmpty.hs +++ b/libraries/base/Data/List/NonEmpty.hs @@ -228,6 +228,8 @@ instance Foldable NonEmpty where foldl1 f ~(a :| as) = foldl f a as foldMap f ~(a :| as) = f a `mappend` foldMap f as fold ~(m :| ms) = m `mappend` fold ms + length = length + toList = toList -- | Extract the first element of the stream. head :: NonEmpty a -> a @@ -507,8 +509,8 @@ nubBy eq (a :| as) = a :| List.nubBy eq (List.filter (\b -> not (eq a b)) as) -- > transpose . transpose /= id transpose :: NonEmpty (NonEmpty a) -> NonEmpty (NonEmpty a) transpose = fmap fromList - . fromList . List.transpose . Foldable.toList - . fmap Foldable.toList + . fromList . List.transpose . toList + . fmap toList -- | 'sortBy' for 'NonEmpty', behaves the same as 'Data.List.sortBy' sortBy :: (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a From git at git.haskell.org Fri Dec 23 22:48:29 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 22:48:29 +0000 (UTC) Subject: [commit: ghc] master: Fix test for T12877 (1b06231) Message-ID: <20161223224829.6F1773A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1b06231ea9063d753a2755a7fc4aeadcc2fc58b9/ghc >--------------------------------------------------------------- commit 1b06231ea9063d753a2755a7fc4aeadcc2fc58b9 Author: Sylvain Henry Date: Fri Dec 23 14:36:10 2016 -0500 Fix test for T12877 Summary: See https://phabricator.haskell.org/rGHCd3b546b1a605 Reviewers: nomeata, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2883 >--------------------------------------------------------------- 1b06231ea9063d753a2755a7fc4aeadcc2fc58b9 testsuite/tests/perf/compiler/all.T | 18 ------------------ testsuite/tests/simplCore/should_compile/Makefile | 4 ++++ .../compiler => simplCore/should_compile}/T12877.hs | 5 +---- testsuite/tests/simplCore/should_compile/all.T | 1 + 4 files changed, 6 insertions(+), 22 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 9c50fa8..2714e86 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -898,21 +898,3 @@ test('T12234', ], compile, ['']) - -test('T12877', - [ stats_num_field('bytes allocated', - [(wordsize(64), 197582248, 5), - # initial: 197582248 (Linux) - ]) - - , compiler_stats_num_field('bytes allocated', - [(platform('x86_64-unknown-mingw32'), 118644280, 5), - # initial: 118644280 - - (wordsize(64), 135979000, 5), - # initial: 135979000 (Linux) - ]), - ], - compile_and_run, - ['-O2']) - diff --git a/testsuite/tests/simplCore/should_compile/Makefile b/testsuite/tests/simplCore/should_compile/Makefile index 5791daf..2efb8bd 100644 --- a/testsuite/tests/simplCore/should_compile/Makefile +++ b/testsuite/tests/simplCore/should_compile/Makefile @@ -167,6 +167,10 @@ T5615: -grep 'remInt#' T5615.dump-simpl grep -c '1999#' T5615.dump-simpl +# When this one works there are no 'plusWord' left at all +T12877: + -('$(TEST_HC)' $(TEST_HC_OPTS) -c -O T12877.hs -ddump-simpl | grep 'plusWord') + T13025: $(RM) -f T13025.o T13025.hi T13025a.o T13025a.hi '$(TEST_HC)' $(TEST_HC_OPTS) -c -O T13025a.hs diff --git a/testsuite/tests/perf/compiler/T12877.hs b/testsuite/tests/simplCore/should_compile/T12877.hs similarity index 98% rename from testsuite/tests/perf/compiler/T12877.hs rename to testsuite/tests/simplCore/should_compile/T12877.hs index 2fc7d58..8a23523 100644 --- a/testsuite/tests/perf/compiler/T12877.hs +++ b/testsuite/tests/simplCore/should_compile/T12877.hs @@ -1,3 +1,4 @@ +module Bug where -- This ugly cascading case reduces to: -- case x of -- 0 -> "0" @@ -111,7 +112,3 @@ test x = case x of 34 -> "0" 35 -> "1" _ -> "n" - -main :: IO () -main = do - putStrLn [last (concat (fmap test [0..12345678]))] diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index e09880f..91a89a8 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -254,6 +254,7 @@ test('T12603', normal, run_command, ['$MAKE -s --no-print-directory T12603']) +test('T12877', normal, run_command, ['$MAKE -s --no-print-directory T12877']) test('T13027', normal, compile, ['']) test('T13025', normal, From git at git.haskell.org Fri Dec 23 22:48:32 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Dec 2016 22:48:32 +0000 (UTC) Subject: [commit: ghc] master: Define MAP_ANONYMOUS on systems that only provide MAP_ANON (2689a16) Message-ID: <20161223224832.390443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2689a1692636521777f007861a484e7064b2d696/ghc >--------------------------------------------------------------- commit 2689a1692636521777f007861a484e7064b2d696 Author: Gracjan Polak Date: Fri Dec 23 14:37:08 2016 -0500 Define MAP_ANONYMOUS on systems that only provide MAP_ANON Reviewers: simonmar, erikd, austin, bgamari Reviewed By: bgamari Subscribers: gracjan, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D2881 GHC Trac Issues: #13005 >--------------------------------------------------------------- 2689a1692636521777f007861a484e7064b2d696 rts/LinkerInternals.h | 10 ++++++++++ rts/linker/M32Alloc.h | 5 ----- 2 files changed, 10 insertions(+), 5 deletions(-) diff --git a/rts/LinkerInternals.h b/rts/LinkerInternals.h index a09d079..76497df 100644 --- a/rts/LinkerInternals.h +++ b/rts/LinkerInternals.h @@ -12,6 +12,10 @@ #include "Rts.h" #include "Hash.h" +#if RTS_LINKER_USE_MMAP +#include +#endif + #include "BeginPrivate.h" typedef void SymbolAddr; @@ -288,6 +292,12 @@ char *cstring_from_section_name( unsigned char* strtab); #endif /* mingw32_HOST_OS */ +/* MAP_ANONYMOUS is MAP_ANON on some systems, + e.g. OS X (before Sierra), OpenBSD etc */ +#if !defined(MAP_ANONYMOUS) && defined(MAP_ANON) +#define MAP_ANONYMOUS MAP_ANON +#endif + /* Which object file format are we targetting? */ #if defined(linux_HOST_OS) || defined(solaris2_HOST_OS) || defined(freebsd_HOST_OS) || defined(kfreebsdgnu_HOST_OS) || defined(dragonfly_HOST_OS) || defined(netbsd_HOST_OS) || defined(openbsd_HOST_OS) || defined(gnu_HOST_OS) # define OBJFORMAT_ELF diff --git a/rts/linker/M32Alloc.h b/rts/linker/M32Alloc.h index db3d8c0..8ec49ca 100644 --- a/rts/linker/M32Alloc.h +++ b/rts/linker/M32Alloc.h @@ -19,11 +19,6 @@ #endif -/* MAP_ANONYMOUS is MAP_ANON on some systems, e.g. OS X, OpenBSD etc */ -#if !defined(MAP_ANONYMOUS) && defined(MAP_ANON) -#define MAP_ANONYMOUS MAP_ANON -#endif - #include "BeginPrivate.h" #if RTS_LINKER_USE_MMAP From git at git.haskell.org Sun Dec 25 14:23:06 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 25 Dec 2016 14:23:06 +0000 (UTC) Subject: [commit: ghc] wip/T9291: Add a CSE pass to Stg (#9291) (e81ce91) Message-ID: <20161225142306.817733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9291 Link : http://ghc.haskell.org/trac/ghc/changeset/e81ce911ded9f1141c66ab5ccc5c8c5cbb0ab560/ghc >--------------------------------------------------------------- commit e81ce911ded9f1141c66ab5ccc5c8c5cbb0ab560 Author: Joachim Breitner Date: Thu Dec 15 10:57:43 2016 -0800 Add a CSE pass to Stg (#9291) This CSE pass only targets data constructor applications. This is probably the best we can do, as function calls and primitive operations might have side-effects. Introduces the flag -fstg-cse, enabled by default with -O. Differential Revision: https://phabricator.haskell.org/D2871 >--------------------------------------------------------------- e81ce911ded9f1141c66ab5ccc5c8c5cbb0ab560 compiler/basicTypes/Id.hs | 6 + compiler/basicTypes/Var.hs | 19 + compiler/coreSyn/CoreSyn.hs | 8 - compiler/coreSyn/TrieMap.hs | 6 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 3 + compiler/simplStg/SimplStg.hs | 30 +- compiler/simplStg/StgCse.hs | 427 +++++++++++++++++++++ compiler/simplStg/UnariseStg.hs | 5 - compiler/stgSyn/StgSyn.hs | 24 +- docs/users_guide/using-optimisation.rst | 8 + testsuite/tests/{ado => simplStg}/Makefile | 0 .../should_run}/Makefile | 0 testsuite/tests/simplStg/should_run/T9291.hs | 58 +++ .../should_run/T9291.stdout} | 1 + testsuite/tests/simplStg/should_run/all.T | 12 + 16 files changed, 578 insertions(+), 30 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e81ce911ded9f1141c66ab5ccc5c8c5cbb0ab560 From git at git.haskell.org Sun Dec 25 14:23:08 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 25 Dec 2016 14:23:08 +0000 (UTC) Subject: [commit: ghc] wip/T9291's head updated: Add a CSE pass to Stg (#9291) (e81ce91) Message-ID: <20161225142308.B338A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T9291' now includes: efc4a16 Allow timeout to kill entire process tree. 7a13f1f Alpha-renaming and white space only f06b71a Fix a bug in ABot handling in CoreArity ea8f91d White space only 9a4af2c Comments only 11306d6 Ensure that even bottoming functions have an unfolding 432f952 Float unboxed expressions by boxing 793ddb6 Tiny refactor in CoreTidy 75e8c30 Propagate evaluated-ness a bit more faithfully ee872d3 Removed dead code in DsCCall.mk_alt b4c3a66 Push coercions in exprIsConApp_maybe 8712148 testsuite: Split out Windows allocations numbers for T12234 f95e669 users-guide: Kill extraneous link 8f89e76 rename: Don't require 'fail' in non-monadic contexts 158530a Add caret diagnostics 46a195f Use python3 for linters 1b06231 Fix test for T12877 94d2cce base: Override Foldable.{toList,length} for NonEmpty 2689a16 Define MAP_ANONYMOUS on systems that only provide MAP_ANON e81ce91 Add a CSE pass to Stg (#9291) From git at git.haskell.org Mon Dec 26 09:17:55 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Dec 2016 09:17:55 +0000 (UTC) Subject: [commit: ghc] branch 'wip/callArityExprIsCheap' created Message-ID: <20161226091755.448123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/callArityExprIsCheap Referencing: 899cf3b9ed306178ab03bd6d97ec86668cc5c76b From git at git.haskell.org Mon Dec 26 09:17:58 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Dec 2016 09:17:58 +0000 (UTC) Subject: [commit: ghc] wip/callArityExprIsCheap: Typo in Call Arity notes (1cf987f) Message-ID: <20161226091758.0CA993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/callArityExprIsCheap Link : http://ghc.haskell.org/trac/ghc/changeset/1cf987f5df07297fa45655d5b372e9dbbbb7dcf0/ghc >--------------------------------------------------------------- commit 1cf987f5df07297fa45655d5b372e9dbbbb7dcf0 Author: Joachim Breitner Date: Sun Dec 25 10:52:52 2016 +0100 Typo in Call Arity notes >--------------------------------------------------------------- 1cf987f5df07297fa45655d5b372e9dbbbb7dcf0 compiler/simplCore/CallArity.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs index a93fe1f..3bd6a43 100644 --- a/compiler/simplCore/CallArity.hs +++ b/compiler/simplCore/CallArity.hs @@ -318,7 +318,7 @@ the analysis of `e2` will not report anything about `x`. To ensure that `callArityBind` does still do the right thing we have to take that into account everytime we would be lookup up `x` in the analysis result of `e2`. * Instead of calling lookupCallArityRes, we return (0, True), indicating - that this variable might be called many times with no variables. + that this variable might be called many times with no arguments. * Instead of checking `calledWith x`, we assume that everything can be called with it. * In the recursive case, when calclulating the `cross_calls`, if there is From git at git.haskell.org Mon Dec 26 09:18:00 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Dec 2016 09:18:00 +0000 (UTC) Subject: [commit: ghc] wip/callArityExprIsCheap: CallArity: Use exprIsCheap to detect thunks (899cf3b) Message-ID: <20161226091800.B9D033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/callArityExprIsCheap Link : http://ghc.haskell.org/trac/ghc/changeset/899cf3b9ed306178ab03bd6d97ec86668cc5c76b/ghc >--------------------------------------------------------------- commit 899cf3b9ed306178ab03bd6d97ec86668cc5c76b Author: Joachim Breitner Date: Mon Dec 26 10:16:55 2016 +0100 CallArity: Use exprIsCheap to detect thunks Originally, everything that is not in WHNF (`exprIsWHNF`) is considered a thunk, not eta-expanded, to avoid losing any sharing. This is also how the published papers on Call Arity describe it. In practice, there are thunks that do a just little work, such as pattern-matching on a variable, and the benefits of eta-expansion likely oughtweigh the cost of doing that repeatedly. Therefore, this implementation of Call Arity considers everything that is not cheap (`exprIsCheap`) as a thunk. >--------------------------------------------------------------- 899cf3b9ed306178ab03bd6d97ec86668cc5c76b compiler/simplCore/CallArity.hs | 19 +++++++++++++++---- 1 file changed, 15 insertions(+), 4 deletions(-) diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs index 3bd6a43..b703c07 100644 --- a/compiler/simplCore/CallArity.hs +++ b/compiler/simplCore/CallArity.hs @@ -15,7 +15,7 @@ import BasicTypes import CoreSyn import Id import CoreArity ( typeArity ) -import CoreUtils ( exprIsHNF, exprIsTrivial ) +import CoreUtils ( exprIsCheap, exprIsTrivial ) --import Outputable import UnVarGraph import Demand @@ -192,7 +192,7 @@ Using the result: Eta-Expansion We use the result of these two analyses to decide whether we can eta-expand the rhs of a let-bound variable. -If the variable is already a function (exprIsHNF), and all calls to the +If the variable is already a function (exprIsCheap), and all calls to the variables have a higher arity than the current manifest arity (i.e. the number of lambdas), expand. @@ -395,6 +395,17 @@ the case for Core! arguments mentioned in the strictness signature. See #10176 for a real-world-example. +Note [What is a thunk] +~~~~~~~~~~~~~~~~~~~~~~ + +Originally, everything that is not in WHNF (`exprIsWHNF`) is considered a +thunk, not eta-expanded, to avoid losing any sharing. This is also how the +published papers on Call Arity describe it. + +In practice, there are thunks that do a just little work, such as +pattern-matching on a variable, and the benefits of eta-expansion likely +oughtweigh the cost of doing that repeatedly. Therefore, this implementation of +Call Arity considers everything that is not cheap (`exprIsCheap`) as a thunk. -} -- Main entry point @@ -533,7 +544,7 @@ callArityBind boring_vars ae_body int (NonRec v rhs) -- (vcat [ppr v, ppr ae_body, ppr int, ppr ae_rhs, ppr safe_arity]) (final_ae, NonRec v' rhs') where - is_thunk = not (exprIsHNF rhs) + is_thunk = not (exprIsCheap rhs) -- see note [What is a thunk] -- If v is boring, we will not find it in ae_body, but always assume (0, False) boring = v `elemVarSet` boring_vars @@ -603,7 +614,7 @@ callArityBind boring_vars ae_body int b@(Rec binds) | otherwise -- We previously analized this with a different arity (or not at all) - = let is_thunk = not (exprIsHNF rhs) + = let is_thunk = not (exprIsCheap rhs) -- see note [What is a thunk] safe_arity | is_thunk = 0 -- See Note [Thunks in recursive groups] | otherwise = new_arity From git at git.haskell.org Mon Dec 26 09:29:17 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Dec 2016 09:29:17 +0000 (UTC) Subject: [commit: ghc] wip/callArityExprIsCheap: CallArity: Use exprIsCheap to detect thunks (0f5b9a6) Message-ID: <20161226092917.11A3D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/callArityExprIsCheap Link : http://ghc.haskell.org/trac/ghc/changeset/0f5b9a6509ebd7176f11b8995043a77243f45612/ghc >--------------------------------------------------------------- commit 0f5b9a6509ebd7176f11b8995043a77243f45612 Author: Joachim Breitner Date: Mon Dec 26 10:16:55 2016 +0100 CallArity: Use exprIsCheap to detect thunks Originally, everything that is not in WHNF (`exprIsWHNF`) is considered a thunk, not eta-expanded, to avoid losing any sharing. This is also how the published papers on Call Arity describe it. In practice, there are thunks that do a just little work, such as pattern-matching on a variable, and the benefits of eta-expansion likely oughtweigh the cost of doing that repeatedly. Therefore, this implementation of Call Arity considers everything that is not cheap (`exprIsCheap`) as a thunk. >--------------------------------------------------------------- 0f5b9a6509ebd7176f11b8995043a77243f45612 compiler/simplCore/CallArity.hs | 19 +++++++++++++++---- testsuite/tests/callarity/unittest/CallArity1.hs | 11 ++++++----- 2 files changed, 21 insertions(+), 9 deletions(-) diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs index 3bd6a43..b703c07 100644 --- a/compiler/simplCore/CallArity.hs +++ b/compiler/simplCore/CallArity.hs @@ -15,7 +15,7 @@ import BasicTypes import CoreSyn import Id import CoreArity ( typeArity ) -import CoreUtils ( exprIsHNF, exprIsTrivial ) +import CoreUtils ( exprIsCheap, exprIsTrivial ) --import Outputable import UnVarGraph import Demand @@ -192,7 +192,7 @@ Using the result: Eta-Expansion We use the result of these two analyses to decide whether we can eta-expand the rhs of a let-bound variable. -If the variable is already a function (exprIsHNF), and all calls to the +If the variable is already a function (exprIsCheap), and all calls to the variables have a higher arity than the current manifest arity (i.e. the number of lambdas), expand. @@ -395,6 +395,17 @@ the case for Core! arguments mentioned in the strictness signature. See #10176 for a real-world-example. +Note [What is a thunk] +~~~~~~~~~~~~~~~~~~~~~~ + +Originally, everything that is not in WHNF (`exprIsWHNF`) is considered a +thunk, not eta-expanded, to avoid losing any sharing. This is also how the +published papers on Call Arity describe it. + +In practice, there are thunks that do a just little work, such as +pattern-matching on a variable, and the benefits of eta-expansion likely +oughtweigh the cost of doing that repeatedly. Therefore, this implementation of +Call Arity considers everything that is not cheap (`exprIsCheap`) as a thunk. -} -- Main entry point @@ -533,7 +544,7 @@ callArityBind boring_vars ae_body int (NonRec v rhs) -- (vcat [ppr v, ppr ae_body, ppr int, ppr ae_rhs, ppr safe_arity]) (final_ae, NonRec v' rhs') where - is_thunk = not (exprIsHNF rhs) + is_thunk = not (exprIsCheap rhs) -- see note [What is a thunk] -- If v is boring, we will not find it in ae_body, but always assume (0, False) boring = v `elemVarSet` boring_vars @@ -603,7 +614,7 @@ callArityBind boring_vars ae_body int b@(Rec binds) | otherwise -- We previously analized this with a different arity (or not at all) - = let is_thunk = not (exprIsHNF rhs) + = let is_thunk = not (exprIsCheap rhs) -- see note [What is a thunk] safe_arity | is_thunk = 0 -- See Note [Thunks in recursive groups] | otherwise = new_arity diff --git a/testsuite/tests/callarity/unittest/CallArity1.hs b/testsuite/tests/callarity/unittest/CallArity1.hs index 6873d32..88f83fd 100644 --- a/testsuite/tests/callarity/unittest/CallArity1.hs +++ b/testsuite/tests/callarity/unittest/CallArity1.hs @@ -24,9 +24,9 @@ import CoreLint import FastString -- Build IDs. use mkTemplateLocal, more predictable than proper uniques -go, go2, x, d, n, y, z, scrut :: Id -[go, go2, x,d, n, y, z, scrut, f] = mkTestIds - (words "go go2 x d n y z scrut f") +go, go2, x, d, n, y, z, scrutf, scruta :: Id +[go, go2, x,d, n, y, z, scrutf, scruta, f] = mkTestIds + (words "go go2 x d n y z scrutf scruta f") [ mkFunTys [intTy, intTy] intTy , mkFunTys [intTy, intTy] intTy , intTy @@ -34,6 +34,7 @@ go, go2, x, d, n, y, z, scrut :: Id , mkFunTys [intTy] intTy , intTy , intTy + , mkFunTys [boolTy] boolTy , boolTy , mkFunTys [intTy, intTy] intTy -- protoypical external function ] @@ -168,7 +169,7 @@ main = do getSessionDynFlags >>= setSessionDynFlags . flip gopt_set Opt_SuppressUniques dflags <- getSessionDynFlags liftIO $ forM_ exprs $ \(n,e) -> do - case lintExpr dflags [f,scrut] e of + case lintExpr dflags [f,scrutf,scruta] e of Just msg -> putMsg dflags (msg $$ text "in" <+> text n) Nothing -> return () putMsg dflags (text n <> char ':') @@ -184,7 +185,7 @@ main = do mkLApps :: Id -> [Integer] -> CoreExpr mkLApps v = mkApps (Var v) . map mkLit -mkACase = mkIfThenElse (Var scrut) +mkACase = mkIfThenElse (mkVarApps (Var scrutf) [scruta]) mkTestId :: Int -> String -> Type -> Id mkTestId i s ty = mkSysLocal (mkFastString s) (mkBuiltinUnique i) ty From git at git.haskell.org Mon Dec 26 14:56:08 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Dec 2016 14:56:08 +0000 (UTC) Subject: [commit: ghc] master: rename: Add note describing #11216 (48a5da9) Message-ID: <20161226145608.6F8953A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/48a5da9ac6abd42e713402bd38612ce6624cac1b/ghc >--------------------------------------------------------------- commit 48a5da9ac6abd42e713402bd38612ce6624cac1b Author: Ben Gamari Date: Fri Dec 23 18:09:40 2016 -0500 rename: Add note describing #11216 >--------------------------------------------------------------- 48a5da9ac6abd42e713402bd38612ce6624cac1b compiler/rename/RnExpr.hs | 26 ++++++++++++++++++++++---- 1 file changed, 22 insertions(+), 4 deletions(-) diff --git a/compiler/rename/RnExpr.hs b/compiler/rename/RnExpr.hs index 5427579..811ecba 100644 --- a/compiler/rename/RnExpr.hs +++ b/compiler/rename/RnExpr.hs @@ -763,6 +763,25 @@ rnStmtsWithFreeVars ctxt rnBody (lstmt@(L loc _) : lstmts) thing_inside ; return (((stmts1 ++ stmts2), thing), fvs) } ---------------------- + +{- +Note [Failing pattern matches in Stmts] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +Many things desugar to HsStmts including monadic things like `do` and `mdo` +statements, pattern guards, and list comprehensions (see 'HsStmtContext' for an +exhaustive list). How we deal with pattern match failure is context-dependent. + + * In the case of list comprehensions and pattern guards we don't need any 'fail' + function; the desugarer ignores the fail function field of 'BindStmt' entirely. + * In the case of monadic contexts (e.g. monad comprehensions, do, and mdo + expressions) we want pattern match failure to be desugared to the appropriate + 'fail' function (either that of Monad or MonadFail, depending on whether + -XMonadFailDesugaring is enabled.) + +At one point we failed to make this distinction, leading to #11216. +-} + rnStmt :: Outputable (body RdrName) => HsStmtContext Name -> (Located (body RdrName) -> RnM (Located (body Name), FreeVars)) @@ -805,13 +824,12 @@ rnStmt ctxt rnBody (L loc (BindStmt pat body _ _ _)) thing_inside ; xMonadFailEnabled <- fmap (xopt LangExt.MonadFailDesugaring) getDynFlags ; let getFailFunction -- For non-monadic contexts (e.g. guard patterns, list - -- comprehensions, etc.) we should not need to fail + -- comprehensions, etc.) we should not need to fail. + -- See Note [Failing pattern matches in Stmts] | not (isMonadFailStmtContext ctxt) - = return (err, emptyFVs) + = return (noSyntaxExpr, emptyFVs) | xMonadFailEnabled = lookupSyntaxName failMName | otherwise = lookupSyntaxName failMName_preMFP - where err = pprPanic "rnStmt: fail function forced" - (text "context:" <+> ppr ctxt) ; (fail_op, fvs2) <- getFailFunction ; rnPat (StmtCtxt ctxt) pat $ \ pat' -> do From git at git.haskell.org Mon Dec 26 15:04:00 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Dec 2016 15:04:00 +0000 (UTC) Subject: [commit: ghc] master: check-ppr: Make --dump the default behavior (9331e33) Message-ID: <20161226150400.1D92F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9331e338a7a8f78c05ef89684ab1a5bb7c79d37d/ghc >--------------------------------------------------------------- commit 9331e338a7a8f78c05ef89684ab1a5bb7c79d37d Author: Ben Gamari Date: Mon Dec 26 10:02:43 2016 -0500 check-ppr: Make --dump the default behavior >--------------------------------------------------------------- 9331e338a7a8f78c05ef89684ab1a5bb7c79d37d utils/check-ppr/Main.hs | 17 ++++++----------- 1 file changed, 6 insertions(+), 11 deletions(-) diff --git a/utils/check-ppr/Main.hs b/utils/check-ppr/Main.hs index c9fac7d..ef39831 100644 --- a/utils/check-ppr/Main.hs +++ b/utils/check-ppr/Main.hs @@ -23,25 +23,21 @@ import qualified Data.Map as Map usage :: String usage = unlines - [ "usage: check-ppr [--dump] (libdir) (file)" + [ "usage: check-ppr (libdir) (file)" , "" , "where libdir is the GHC library directory (e.g. the output of" , "ghc --print-libdir) and file is the file to parse." - , "The --dump flag causes check-ppr to produce .new and .old files" - , "containing dumps of the new and old ASTs in the event of a match" - , "failure." ] main :: IO() main = do args <- getArgs case args of - [libdir,fileName] -> testOneFile libdir fileName False - ["--dump", libdir,fileName] -> testOneFile libdir fileName True + [libdir,fileName] -> testOneFile libdir fileName _ -> putStrLn usage -testOneFile :: FilePath -> String -> Bool -> IO () -testOneFile libdir fileName dumpOldNew = do +testOneFile :: FilePath -> String -> IO () +testOneFile libdir fileName = do p <- parseOneFile libdir fileName let origAst = showAstData 0 (pm_parsed_source p) @@ -51,6 +47,7 @@ testOneFile libdir fileName dumpOldNew = do newFile = dropExtension fileName <.> "ppr" <.> takeExtension fileName astFile = fileName <.> "ast" + newAstFile = fileName <.> "ast.new" writeFile astFile origAst writeFile newFile pped @@ -58,6 +55,7 @@ testOneFile libdir fileName dumpOldNew = do p' <- parseOneFile libdir newFile let newAstStr = showAstData 0 (pm_parsed_source p') + writeFile newAstFile newAstStr if origAst == newAstStr then do @@ -69,9 +67,6 @@ testOneFile libdir fileName dumpOldNew = do putStrLn origAst putStrLn "\n===================================\nNew\n\n" putStrLn newAstStr - when dumpOldNew $ do - writeFile (fileName <.> "old") origAst - writeFile (fileName <.> "new") newAstStr exitFailure From git at git.haskell.org Mon Dec 26 16:27:13 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Dec 2016 16:27:13 +0000 (UTC) Subject: [commit: ghc] master: Remove redudant import from check-ppr (3c9fbba) Message-ID: <20161226162713.95BC53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3c9fbbac3a34700565b1d51df67444fda149952f/ghc >--------------------------------------------------------------- commit 3c9fbbac3a34700565b1d51df67444fda149952f Author: Matthew Pickering Date: Mon Dec 26 16:26:49 2016 +0000 Remove redudant import from check-ppr >--------------------------------------------------------------- 3c9fbbac3a34700565b1d51df67444fda149952f utils/check-ppr/Main.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/utils/check-ppr/Main.hs b/utils/check-ppr/Main.hs index ef39831..c968b83 100644 --- a/utils/check-ppr/Main.hs +++ b/utils/check-ppr/Main.hs @@ -1,7 +1,6 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE RankNTypes #-} -import Control.Monad (when) import Data.Data hiding (Fixity) import Data.List import Bag From git at git.haskell.org Mon Dec 26 20:32:51 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Dec 2016 20:32:51 +0000 (UTC) Subject: [commit: ghc] branch 'wip/callArityExprIsCheap' deleted Message-ID: <20161226203251.382703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/callArityExprIsCheap From git at git.haskell.org Mon Dec 26 20:34:04 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Dec 2016 20:34:04 +0000 (UTC) Subject: [commit: ghc] master: CallArity: Use exprIsCheap to detect thunks (815099c) Message-ID: <20161226203404.B4D733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/815099cce8f183d49305c9d40c8ed699c178108c/ghc >--------------------------------------------------------------- commit 815099cce8f183d49305c9d40c8ed699c178108c Author: Joachim Breitner Date: Mon Dec 26 10:16:55 2016 +0100 CallArity: Use exprIsCheap to detect thunks Originally, everything that is not in WHNF (`exprIsWHNF`) is considered a thunk, not eta-expanded, to avoid losing any sharing. This is also how the published papers on Call Arity describe it. In practice, there are thunks that do a just little work, such as pattern-matching on a variable, and the benefits of eta-expansion likely oughtweigh the cost of doing that repeatedly. Therefore, this implementation of Call Arity considers everything that is not cheap (`exprIsCheap`) as a thunk. Nofib reports -2.58% allocations for scs and -40.93% allocation for wheel-sieve1; the latter has - 2.92% runtime. >--------------------------------------------------------------- 815099cce8f183d49305c9d40c8ed699c178108c compiler/simplCore/CallArity.hs | 21 ++++++++++++++++----- testsuite/tests/callarity/unittest/CallArity1.hs | 11 ++++++----- 2 files changed, 22 insertions(+), 10 deletions(-) diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs index a93fe1f..b703c07 100644 --- a/compiler/simplCore/CallArity.hs +++ b/compiler/simplCore/CallArity.hs @@ -15,7 +15,7 @@ import BasicTypes import CoreSyn import Id import CoreArity ( typeArity ) -import CoreUtils ( exprIsHNF, exprIsTrivial ) +import CoreUtils ( exprIsCheap, exprIsTrivial ) --import Outputable import UnVarGraph import Demand @@ -192,7 +192,7 @@ Using the result: Eta-Expansion We use the result of these two analyses to decide whether we can eta-expand the rhs of a let-bound variable. -If the variable is already a function (exprIsHNF), and all calls to the +If the variable is already a function (exprIsCheap), and all calls to the variables have a higher arity than the current manifest arity (i.e. the number of lambdas), expand. @@ -318,7 +318,7 @@ the analysis of `e2` will not report anything about `x`. To ensure that `callArityBind` does still do the right thing we have to take that into account everytime we would be lookup up `x` in the analysis result of `e2`. * Instead of calling lookupCallArityRes, we return (0, True), indicating - that this variable might be called many times with no variables. + that this variable might be called many times with no arguments. * Instead of checking `calledWith x`, we assume that everything can be called with it. * In the recursive case, when calclulating the `cross_calls`, if there is @@ -395,6 +395,17 @@ the case for Core! arguments mentioned in the strictness signature. See #10176 for a real-world-example. +Note [What is a thunk] +~~~~~~~~~~~~~~~~~~~~~~ + +Originally, everything that is not in WHNF (`exprIsWHNF`) is considered a +thunk, not eta-expanded, to avoid losing any sharing. This is also how the +published papers on Call Arity describe it. + +In practice, there are thunks that do a just little work, such as +pattern-matching on a variable, and the benefits of eta-expansion likely +oughtweigh the cost of doing that repeatedly. Therefore, this implementation of +Call Arity considers everything that is not cheap (`exprIsCheap`) as a thunk. -} -- Main entry point @@ -533,7 +544,7 @@ callArityBind boring_vars ae_body int (NonRec v rhs) -- (vcat [ppr v, ppr ae_body, ppr int, ppr ae_rhs, ppr safe_arity]) (final_ae, NonRec v' rhs') where - is_thunk = not (exprIsHNF rhs) + is_thunk = not (exprIsCheap rhs) -- see note [What is a thunk] -- If v is boring, we will not find it in ae_body, but always assume (0, False) boring = v `elemVarSet` boring_vars @@ -603,7 +614,7 @@ callArityBind boring_vars ae_body int b@(Rec binds) | otherwise -- We previously analized this with a different arity (or not at all) - = let is_thunk = not (exprIsHNF rhs) + = let is_thunk = not (exprIsCheap rhs) -- see note [What is a thunk] safe_arity | is_thunk = 0 -- See Note [Thunks in recursive groups] | otherwise = new_arity diff --git a/testsuite/tests/callarity/unittest/CallArity1.hs b/testsuite/tests/callarity/unittest/CallArity1.hs index 6873d32..88f83fd 100644 --- a/testsuite/tests/callarity/unittest/CallArity1.hs +++ b/testsuite/tests/callarity/unittest/CallArity1.hs @@ -24,9 +24,9 @@ import CoreLint import FastString -- Build IDs. use mkTemplateLocal, more predictable than proper uniques -go, go2, x, d, n, y, z, scrut :: Id -[go, go2, x,d, n, y, z, scrut, f] = mkTestIds - (words "go go2 x d n y z scrut f") +go, go2, x, d, n, y, z, scrutf, scruta :: Id +[go, go2, x,d, n, y, z, scrutf, scruta, f] = mkTestIds + (words "go go2 x d n y z scrutf scruta f") [ mkFunTys [intTy, intTy] intTy , mkFunTys [intTy, intTy] intTy , intTy @@ -34,6 +34,7 @@ go, go2, x, d, n, y, z, scrut :: Id , mkFunTys [intTy] intTy , intTy , intTy + , mkFunTys [boolTy] boolTy , boolTy , mkFunTys [intTy, intTy] intTy -- protoypical external function ] @@ -168,7 +169,7 @@ main = do getSessionDynFlags >>= setSessionDynFlags . flip gopt_set Opt_SuppressUniques dflags <- getSessionDynFlags liftIO $ forM_ exprs $ \(n,e) -> do - case lintExpr dflags [f,scrut] e of + case lintExpr dflags [f,scrutf,scruta] e of Just msg -> putMsg dflags (msg $$ text "in" <+> text n) Nothing -> return () putMsg dflags (text n <> char ':') @@ -184,7 +185,7 @@ main = do mkLApps :: Id -> [Integer] -> CoreExpr mkLApps v = mkApps (Var v) . map mkLit -mkACase = mkIfThenElse (Var scrut) +mkACase = mkIfThenElse (mkVarApps (Var scrutf) [scruta]) mkTestId :: Int -> String -> Type -> Id mkTestId i s ty = mkSysLocal (mkFastString s) (mkBuiltinUnique i) ty From git at git.haskell.org Tue Dec 27 08:42:09 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Dec 2016 08:42:09 +0000 (UTC) Subject: [commit: ghc] master: Expand I/O CP in comments (d2788ab) Message-ID: <20161227084209.DF6213A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d2788ab551fb9dc17f3d4d67ef843a5f3b56f9c6/ghc >--------------------------------------------------------------- commit d2788ab551fb9dc17f3d4d67ef843a5f3b56f9c6 Author: Joachim Breitner Date: Tue Dec 27 09:41:19 2016 +0100 Expand I/O CP in comments as suggested by @gracjan at https://github.com/ghc/ghc/commit/efc4a1661f0fc1004a4b7b0914f3d3a08c2e791a#commitcomment-20284337 >--------------------------------------------------------------- d2788ab551fb9dc17f3d4d67ef843a5f3b56f9c6 testsuite/timeout/timeout.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/timeout/timeout.hs b/testsuite/timeout/timeout.hs index 4e97c5c..d466495 100644 --- a/testsuite/timeout/timeout.hs +++ b/testsuite/timeout/timeout.hs @@ -110,8 +110,8 @@ run secs cmd = when (ioPort == nullPtr) $ errorWin "createCompletionPort, cannot continue." -- We're explicitly turning off handle inheritance to prevent misc handles - -- from being inherited by the child. Notable we don't want the I/O CP and - -- Job handles to be inherited. So we mark them as non-inheritable. + -- from being inherited by the child. Notable we don't want the I/O Completion + -- Ports and Job handles to be inherited. So we mark them as non-inheritable. setHandleInformation job cHANDLE_FLAG_INHERIT 0 setHandleInformation job cHANDLE_FLAG_INHERIT 0 From git at git.haskell.org Tue Dec 27 17:44:46 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Dec 2016 17:44:46 +0000 (UTC) Subject: [commit: packages/array] master: Fix overflow check (6e110fe) Message-ID: <20161227174446.B8A103A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array On branch : master Link : http://git.haskell.org/packages/array.git/commitdiff/6e110fe4193472c2e47aa0563362f95dd8bca37b >--------------------------------------------------------------- commit 6e110fe4193472c2e47aa0563362f95dd8bca37b Author: Ben Gamari Date: Mon Dec 26 13:13:26 2016 -0500 Fix overflow check As akio points out, the fix to #229 which I authored previously was blatantly wrong. >--------------------------------------------------------------- 6e110fe4193472c2e47aa0563362f95dd8bca37b Data/Array/Base.hs | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/Data/Array/Base.hs b/Data/Array/Base.hs index c88e272..43963eb 100644 --- a/Data/Array/Base.hs +++ b/Data/Array/Base.hs @@ -32,7 +32,7 @@ import GHC.Arr ( STArray ) import qualified GHC.Arr as Arr import qualified GHC.Arr as ArrST import GHC.ST ( ST(..), runST ) -import GHC.Base ( IO(..) ) +import GHC.Base ( IO(..), divInt# ) import GHC.Exts import GHC.Ptr ( nullPtr, nullFunPtr ) import GHC.Stable ( StablePtr(..) ) @@ -1370,10 +1370,12 @@ fLOAT_SCALE n# = safe_scale scale# n# where !(I# scale#) = SIZEOF_HSFLOAT safe_scale :: Int# -> Int# -> Int# safe_scale scale# n# - | isTrue# (res# >=# n#) = res# - | otherwise = error "Data.Array.Base.safe_scale: Overflow" + | not overflow = res# + | otherwise = error "Data.Array.Base.safe_scale: Overflow" where !res# = scale# *# n# + !overflow = isTrue# (maxN# `divInt#` scale# <# n#) + !(I# maxN#) = maxBound bOOL_INDEX :: Int# -> Int# From git at git.haskell.org Tue Dec 27 17:45:00 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Dec 2016 17:45:00 +0000 (UTC) Subject: [commit: ghc] master: Bump array submodule (f3b99c7) Message-ID: <20161227174500.75A523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f3b99c75fef7fc946a27de63edb5e6d6ad5a22be/ghc >--------------------------------------------------------------- commit f3b99c75fef7fc946a27de63edb5e6d6ad5a22be Author: Ben Gamari Date: Mon Dec 26 13:14:38 2016 -0500 Bump array submodule Fixes overflow check from fix to #229. >--------------------------------------------------------------- f3b99c75fef7fc946a27de63edb5e6d6ad5a22be libraries/array | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/array b/libraries/array index b8a8d09..6e110fe 160000 --- a/libraries/array +++ b/libraries/array @@ -1 +1 @@ -Subproject commit b8a8d09ddc20a9c9d99bd03b136718b543edb877 +Subproject commit 6e110fe4193472c2e47aa0563362f95dd8bca37b From git at git.haskell.org Tue Dec 27 17:45:03 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Dec 2016 17:45:03 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: Skip failing tests on PowerPC 64-bit (4dec7d1) Message-ID: <20161227174503.3E77F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4dec7d191fbc26276cc2c8306d9d03e71e277979/ghc >--------------------------------------------------------------- commit 4dec7d191fbc26276cc2c8306d9d03e71e277979 Author: Peter Trommler Date: Mon Dec 26 10:04:54 2016 -0500 Testsuite: Skip failing tests on PowerPC 64-bit The Power ISA says the result of a division by zero is undefined. So ignore stdout on PowerPC 64-bit systems. Disable ext-interp tests on 64-bit PowerPC. We don't have support for PowerPC 64-bit ELF in the RTS linker, which is needed for the external interpreter. Test Plan: ./validate Reviewers: austin, simonmar, hvr, erikd, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2782 >--------------------------------------------------------------- 4dec7d191fbc26276cc2c8306d9d03e71e277979 configure.ac | 12 ++++++++++++ mk/config.mk.in | 2 +- rts/Linker.c | 20 +++++++++++++------- rts/linker/Elf.c | 4 ++++ settings.in | 1 + testsuite/config/ghc | 3 +++ testsuite/tests/ghci/scripts/all.T | 3 ++- testsuite/tests/rts/all.T | 4 ++-- testsuite/tests/th/all.T | 5 +++-- 9 files changed, 41 insertions(+), 13 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4dec7d191fbc26276cc2c8306d9d03e71e277979 From git at git.haskell.org Tue Dec 27 17:45:05 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Dec 2016 17:45:05 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Fix T13025 (88f5add) Message-ID: <20161227174505.F20A93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/88f5add0280788d424c9df5f751a73e73a1a4284/ghc >--------------------------------------------------------------- commit 88f5add0280788d424c9df5f751a73e73a1a4284 Author: Ben Gamari Date: Tue Dec 27 12:08:24 2016 -0500 testsuite: Fix T13025 It relied on `wc`, which produces slightly different format on OS X and Linux. Instead use `grep -c` which appears to be supported on both platforms and produces consistent output. >--------------------------------------------------------------- 88f5add0280788d424c9df5f751a73e73a1a4284 testsuite/tests/simplCore/should_compile/Makefile | 2 +- testsuite/tests/simplCore/should_compile/T13025.stdout | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/simplCore/should_compile/Makefile b/testsuite/tests/simplCore/should_compile/Makefile index 2efb8bd..7d5d5b9 100644 --- a/testsuite/tests/simplCore/should_compile/Makefile +++ b/testsuite/tests/simplCore/should_compile/Makefile @@ -174,5 +174,5 @@ T12877: T13025: $(RM) -f T13025.o T13025.hi T13025a.o T13025a.hi '$(TEST_HC)' $(TEST_HC_OPTS) -c -O T13025a.hs - '$(TEST_HC)' $(TEST_HC_OPTS) -c -O T13025.hs -ddump-simpl | grep HEq_sc | wc + -'$(TEST_HC)' $(TEST_HC_OPTS) -c -O T13025.hs -ddump-simpl | grep -c HEq_sc # No lines should match 'HEq_sc' so wc should output zeros diff --git a/testsuite/tests/simplCore/should_compile/T13025.stdout b/testsuite/tests/simplCore/should_compile/T13025.stdout index 7d1413f..573541a 100644 --- a/testsuite/tests/simplCore/should_compile/T13025.stdout +++ b/testsuite/tests/simplCore/should_compile/T13025.stdout @@ -1 +1 @@ - 0 0 0 +0 From git at git.haskell.org Wed Dec 28 10:34:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Dec 2016 10:34:26 +0000 (UTC) Subject: [commit: ghc] master: Fix various issues with testsuite code on Windows (a370440) Message-ID: <20161228103426.0CBEA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a3704409acc3bd237d3e872f640686918fb51f5f/ghc >--------------------------------------------------------------- commit a3704409acc3bd237d3e872f640686918fb51f5f Author: Tamar Christina Date: Wed Dec 28 10:04:28 2016 +0000 Fix various issues with testsuite code on Windows Summary: Previously we would make direct calls to `diff` using `os.system`. On Windows `os.system` is implemented using the standard idiom `CreateProcess .. WaitForSingleObject ..`. This again runs afoul with the `_exec` behaviour on Windows. So we ran into some trouble where sometimes `diff` would return before it's done. On tests which run multiple ways, such as `8086` what happens is that we think the diff is done and continue. The next way tries to set things up again by removing any previous directory. This would then fail with and error saying the directory can't be removed. Which is true, because the previous diff code/child is still running. We shouldn't make any external calls to anything using `os.system`. Instead just use `runCmd` which uses `timeout`. This also ensures that if we hit the cygwin bug where diff or any other utility hangs, we kill it and continue and not hang the entire test and leave hanging processes. Further more we also: Ignore error lines from `removeFile` from tools in the testsuite. This is a rather large hammer to work around the fact that `hsc2hs` often tries to remove it's own file too early. When this is patched the workaround can be removed. See Trac #9775 We mark `prog003` as skip. Since this test randomly fails and passes. For stability it's disabled but it is a genuine bug which we should find. It's something with interface files being overwritten. See Trac #11317 when `rmtree` hits a readonly file, the `onerror` handler is raised afterwards but not during the tree walk. It doesn't allow you to recover and continue as we thought. Instead you have to explicitly start again. This is why sometimes even though we call `cleanup` before `os.mkdirs`, it would sometimes fail with an error that the folder already exists. So we now do a second walk. A new verbosity level (4) will strip the silent flags from `MAKE` invocations so you can actually see what's going on. Test Plan: ./validate on build bots. Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: mpickering, thomie, #ghc_windows_task_force Differential Revision: https://phabricator.haskell.org/D2894 GHC Trac Issues: #12661, #11317, #9775 >--------------------------------------------------------------- a3704409acc3bd237d3e872f640686918fb51f5f testsuite/driver/testlib.py | 110 ++++++++++++++++++++++----------- testsuite/tests/ghci/prog003/prog003.T | 6 +- testsuite/timeout/timeout.hs | 4 +- 3 files changed, 81 insertions(+), 39 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a3704409acc3bd237d3e872f640686918fb51f5f From git at git.haskell.org Wed Dec 28 15:14:41 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Dec 2016 15:14:41 +0000 (UTC) Subject: [commit: ghc] branch 'wip/D2899' created Message-ID: <20161228151441.C01AF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/D2899 Referencing: 035605f29cf8f4d324ad7b080850a8d6b38f30cb From git at git.haskell.org Wed Dec 28 15:14:44 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Dec 2016 15:14:44 +0000 (UTC) Subject: [commit: ghc] wip/D2899: Generic and Generic1 instances for tuples (035605f) Message-ID: <20161228151444.804833A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/D2899 Link : http://ghc.haskell.org/trac/ghc/changeset/035605f29cf8f4d324ad7b080850a8d6b38f30cb/ghc >--------------------------------------------------------------- commit 035605f29cf8f4d324ad7b080850a8d6b38f30cb Author: Vladislav Zavialov Date: Wed Dec 28 10:14:21 2016 -0500 Generic and Generic1 instances for tuples Add lacking Generic and Generic1 instances for tuples of size up to 62, which is the size limit for tuples in GHC. Reviewers: austin, hvr, bgamari Subscribers: RyanGlScott, thomie Differential Revision: https://phabricator.haskell.org/D2899 >--------------------------------------------------------------- 035605f29cf8f4d324ad7b080850a8d6b38f30cb libraries/base/GHC/Generics.hs | 110 +++++++++++++++++++++++++++++++++++++++++ 1 file changed, 110 insertions(+) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 035605f29cf8f4d324ad7b080850a8d6b38f30cb From git at git.haskell.org Thu Dec 29 18:26:07 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Dec 2016 18:26:07 +0000 (UTC) Subject: [commit: ghc] wip/T9291: Add a CSE pass to Stg (#9291) (aac08a0) Message-ID: <20161229182607.B4C753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9291 Link : http://ghc.haskell.org/trac/ghc/changeset/aac08a0f37442a79096d7d2392f34b42ee5da2bb/ghc >--------------------------------------------------------------- commit aac08a0f37442a79096d7d2392f34b42ee5da2bb Author: Joachim Breitner Date: Thu Dec 15 10:57:43 2016 -0800 Add a CSE pass to Stg (#9291) This CSE pass only targets data constructor applications. This is probably the best we can do, as function calls and primitive operations might have side-effects. Introduces the flag -fstg-cse, enabled by default with -O. Differential Revision: https://phabricator.haskell.org/D2871 >--------------------------------------------------------------- aac08a0f37442a79096d7d2392f34b42ee5da2bb compiler/basicTypes/Id.hs | 6 + compiler/basicTypes/Var.hs | 19 + compiler/coreSyn/CoreSyn.hs | 8 - compiler/coreSyn/TrieMap.hs | 6 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 3 + compiler/simplStg/SimplStg.hs | 30 +- compiler/simplStg/StgCse.hs | 427 +++++++++++++++++++++ compiler/simplStg/UnariseStg.hs | 5 - compiler/stgSyn/StgSyn.hs | 24 +- docs/users_guide/using-optimisation.rst | 8 + testsuite/tests/{ado => simplStg}/Makefile | 0 .../should_run}/Makefile | 0 testsuite/tests/simplStg/should_run/T9291.hs | 58 +++ .../should_run/T9291.stdout} | 1 + testsuite/tests/simplStg/should_run/all.T | 12 + 16 files changed, 578 insertions(+), 30 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc aac08a0f37442a79096d7d2392f34b42ee5da2bb From git at git.haskell.org Thu Dec 29 18:26:09 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Dec 2016 18:26:09 +0000 (UTC) Subject: [commit: ghc] wip/T9291's head updated: Add a CSE pass to Stg (#9291) (aac08a0) Message-ID: <20161229182609.D71973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T9291' now includes: 48a5da9 rename: Add note describing #11216 9331e33 check-ppr: Make --dump the default behavior 3c9fbba Remove redudant import from check-ppr 815099c CallArity: Use exprIsCheap to detect thunks d2788ab Expand I/O CP in comments 88f5add testsuite: Fix T13025 4dec7d1 Testsuite: Skip failing tests on PowerPC 64-bit f3b99c7 Bump array submodule a370440 Fix various issues with testsuite code on Windows aac08a0 Add a CSE pass to Stg (#9291)