From git at git.haskell.org Mon May 1 00:21:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 May 2017 00:21:57 +0000 (UTC) Subject: [commit: ghc] branch 'wip/rwbarton-seq-unf' created Message-ID: <20170501002157.1BFCA3A588@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/rwbarton-seq-unf Referencing: 9ca83a67bb88682f0382323ffb6a7481cf02e703 From git at git.haskell.org Mon May 1 00:21:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 May 2017 00:21:59 +0000 (UTC) Subject: [commit: ghc] wip/rwbarton-seq-unf: WIP: Force stable unfoldings in megaSeqIdInfo (9ca83a6) Message-ID: <20170501002159.D6F4D3A588@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rwbarton-seq-unf Link : http://ghc.haskell.org/trac/ghc/changeset/9ca83a67bb88682f0382323ffb6a7481cf02e703/ghc >--------------------------------------------------------------- commit 9ca83a67bb88682f0382323ffb6a7481cf02e703 Author: Reid Barton Date: Sun Apr 30 20:21:43 2017 -0400 WIP: Force stable unfoldings in megaSeqIdInfo >--------------------------------------------------------------- 9ca83a67bb88682f0382323ffb6a7481cf02e703 compiler/coreSyn/CoreSeq.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/compiler/coreSyn/CoreSeq.hs b/compiler/coreSyn/CoreSeq.hs index d426bd3..bb2ca04 100644 --- a/compiler/coreSyn/CoreSeq.hs +++ b/compiler/coreSyn/CoreSeq.hs @@ -28,7 +28,7 @@ megaSeqIdInfo info -- Omitting this improves runtimes a little, presumably because -- some unfoldings are not calculated at all --- seqUnfolding (unfoldingInfo info) `seq` + seqUnfolding (unfoldingInfo info) `seq` seqDemand (demandInfo info) `seq` seqStrictSig (strictnessInfo info) `seq` @@ -101,7 +101,8 @@ seqUnfolding :: Unfolding -> () seqUnfolding (CoreUnfolding { uf_tmpl = e, uf_is_top = top, uf_is_value = b1, uf_is_work_free = b2, uf_expandable = b3, uf_is_conlike = b4, - uf_guidance = g}) + uf_guidance = g, uf_src = src}) + | isStableSource src = seqExpr e `seq` top `seq` b1 `seq` b2 `seq` b3 `seq` b4 `seq` seqGuidance g seqUnfolding _ = () From git at git.haskell.org Mon May 1 03:04:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 May 2017 03:04:42 +0000 (UTC) Subject: [commit: ghc] master: Disable -Wcpp-undef for now (46923b6) Message-ID: <20170501030442.469183A588@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/46923b6df17c9514b6b705119c8273086ba0ace5/ghc >--------------------------------------------------------------- commit 46923b6df17c9514b6b705119c8273086ba0ace5 Author: Ben Gamari Date: Sun Apr 30 22:41:38 2017 -0400 Disable -Wcpp-undef for now We at very least need to upstream a patch for the time submodule to compile on OS X. >--------------------------------------------------------------- 46923b6df17c9514b6b705119c8273086ba0ace5 mk/warnings.mk | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/mk/warnings.mk b/mk/warnings.mk index 3c4c26d..af5f4f5 100644 --- a/mk/warnings.mk +++ b/mk/warnings.mk @@ -8,8 +8,8 @@ SRC_HC_OPTS += -Wall # isn't supported yet (https://ghc.haskell.org/trac/ghc/wiki/Design/Warnings). # # See Note [Stage number in build variables] in mk/config.mk.in. -SRC_HC_OPTS_STAGE1 += $(WERROR) -Wcpp-undef -SRC_HC_OPTS_STAGE2 += $(WERROR) -Wcpp-undef +SRC_HC_OPTS_STAGE1 += $(WERROR) #-Wcpp-undef +SRC_HC_OPTS_STAGE2 += $(WERROR) #-Wcpp-undef ifneq "$(GccIsClang)" "YES" From git at git.haskell.org Mon May 1 03:04:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 May 2017 03:04:44 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Widen acceptance window of T13379 (821a9f9) Message-ID: <20170501030444.F33B43A588@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/821a9f98448a272ab3b27494e5174223e86cfa4e/ghc >--------------------------------------------------------------- commit 821a9f98448a272ab3b27494e5174223e86cfa4e Author: Ben Gamari Date: Sun Apr 30 09:57:07 2017 -0400 testsuite: Widen acceptance window of T13379 >--------------------------------------------------------------- 821a9f98448a272ab3b27494e5174223e86cfa4e 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 55b577a..3acc511 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -1082,8 +1082,9 @@ test('T12707', test('T13379', [ compiler_stats_num_field('bytes allocated', - [(wordsize(64), 411597856, 5), + [(wordsize(64), 411597856, 10), # initial: 411597856 + # widen window to 10%, Darwin had 449080520, a 9.1% difference ]), ], compile, From git at git.haskell.org Mon May 1 03:04:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 May 2017 03:04:47 +0000 (UTC) Subject: [commit: ghc] master: Update broken nm message (0ff7bc8) Message-ID: <20170501030447.AE2E73A588@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0ff7bc8a6a7705425f99680178f5d07c5cdc55d0/ghc >--------------------------------------------------------------- commit 0ff7bc8a6a7705425f99680178f5d07c5cdc55d0 Author: Alex Biehl Date: Sun Apr 30 16:24:30 2017 +0200 Update broken nm message 9373994acaf1b73fe0e7cf8e03594c63cec8d235 killed the `--with-*` arguments for `configure`. >--------------------------------------------------------------- 0ff7bc8a6a7705425f99680178f5d07c5cdc55d0 configure.ac | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/configure.ac b/configure.ac index 46e37ab..0a0f790 100644 --- a/configure.ac +++ b/configure.ac @@ -526,7 +526,7 @@ then echo echo "Try re-running configure with:" echo - echo ' ./configure --with-nm=$(xcrun --find nm-classic)' + echo ' NM=$(xcrun --find nm-classic) ./configure' echo exit 1 ;; From git at git.haskell.org Mon May 1 14:52:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 May 2017 14:52:22 +0000 (UTC) Subject: [commit: ghc] master: Ignore ANN pragmas with no TH and no external interpreter. (7567b9d) Message-ID: <20170501145222.5DF863A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7567b9ddba7c4304e8d0226e9bf82a054f37ce91/ghc >--------------------------------------------------------------- commit 7567b9ddba7c4304e8d0226e9bf82a054f37ce91 Author: Shea Levy Date: Sun Apr 30 23:20:54 2017 -0400 Ignore ANN pragmas with no TH and no external interpreter. Reviewers: hvr, austin, bgamari, RyanGlScott Reviewed By: bgamari Subscribers: angerman, RyanGlScott, rwbarton, thomie GHC Trac Issues: #13609 Differential Revision: https://phabricator.haskell.org/D3496 >--------------------------------------------------------------- 7567b9ddba7c4304e8d0226e9bf82a054f37ce91 compiler/typecheck/TcAnnotations.hs | 25 ++++++++++++++++++++++++- 1 file changed, 24 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcAnnotations.hs b/compiler/typecheck/TcAnnotations.hs index 7b3cc65..43d2970 100644 --- a/compiler/typecheck/TcAnnotations.hs +++ b/compiler/typecheck/TcAnnotations.hs @@ -22,8 +22,31 @@ import TcRnMonad import SrcLoc import Outputable +-- Some platforms don't support the external interpreter, and +-- compilation on those platforms shouldn't fail just due to +-- annotations +#ifndef GHCI tcAnnotations :: [LAnnDecl Name] -> TcM [Annotation] -tcAnnotations anns = mapM tcAnnotation anns +tcAnnotations anns = do + dflags <- getDynFlags + case gopt Opt_ExternalInterpreter dflags of + True -> tcAnnotations' anns + False -> warnAnns anns +warnAnns :: [LAnnDecl Name] -> TcM [Annotation] +--- No GHCI; emit a warning (not an error) and ignore. cf Trac #4268 +warnAnns [] = return [] +warnAnns anns@(L loc _ : _) + = do { setSrcSpan loc $ addWarnTc NoReason $ + (text "Ignoring Ann annotation" <> plural anns <> comma + <+> text "because this is a stage-1 compiler without -fexternal-interpreter or doesn't support GHCi") + ; return [] } +#else +tcAnnotations :: [LAnnDecl Name] -> TcM [Annotation] +tcAnnotations = tcAnnotations' +#endif + +tcAnnotations' :: [LAnnDecl Name] -> TcM [Annotation] +tcAnnotations' anns = mapM tcAnnotation anns tcAnnotation :: LAnnDecl Name -> TcM Annotation tcAnnotation (L loc ann@(HsAnnotation _ provenance expr)) = do From git at git.haskell.org Mon May 1 14:52:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 May 2017 14:52:25 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add test for #13609 (18fbb9d) Message-ID: <20170501145225.EC96E3A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/18fbb9d32cbc157e3bbd235e392f1625f77321e3/ghc >--------------------------------------------------------------- commit 18fbb9d32cbc157e3bbd235e392f1625f77321e3 Author: Ben Gamari Date: Sun Apr 30 23:19:26 2017 -0400 testsuite: Add test for #13609 >--------------------------------------------------------------- 18fbb9d32cbc157e3bbd235e392f1625f77321e3 testsuite/tests/stage1/T13609.hs | 5 +++++ testsuite/tests/stage1/T13609.stderr | 3 +++ testsuite/tests/stage1/all.T | 1 + 3 files changed, 9 insertions(+) diff --git a/testsuite/tests/stage1/T13609.hs b/testsuite/tests/stage1/T13609.hs new file mode 100644 index 0000000..e67eb32 --- /dev/null +++ b/testsuite/tests/stage1/T13609.hs @@ -0,0 +1,5 @@ +module M where + +{-# ANN myId "HLint: ignore" #-} +myId :: a -> a +myId x = x diff --git a/testsuite/tests/stage1/T13609.stderr b/testsuite/tests/stage1/T13609.stderr new file mode 100644 index 0000000..0a3c1cd --- /dev/null +++ b/testsuite/tests/stage1/T13609.stderr @@ -0,0 +1,3 @@ + +T13609.hs:3:1: warning: + Ignoring Ann annotation, because this is a stage-1 compiler without -fexternal-interpreter or doesn't support GHCi diff --git a/testsuite/tests/stage1/all.T b/testsuite/tests/stage1/all.T index a7f01b3..40bb274 100644 --- a/testsuite/tests/stage1/all.T +++ b/testsuite/tests/stage1/all.T @@ -4,3 +4,4 @@ setTestOpts(unless(config.stage == 1, skip)) # Test with stage1 compiler, see ticket:10382#comment:20. test('T2632', normal, compile, ['-XTemplateHaskellQuotes -package template-haskell']) +test('T13609', normal, compile, ['']) From git at git.haskell.org Mon May 1 15:10:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 May 2017 15:10:48 +0000 (UTC) Subject: [commit: ghc] master: Fix capitalization in message for #13609 (c04bd55) Message-ID: <20170501151048.BD1243A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c04bd55a8daaf254436cef02934215d0b4ccfa2f/ghc >--------------------------------------------------------------- commit c04bd55a8daaf254436cef02934215d0b4ccfa2f Author: Ben Gamari Date: Mon May 1 11:06:08 2017 -0400 Fix capitalization in message for #13609 I had meant to do this before merging but forgot. >--------------------------------------------------------------- c04bd55a8daaf254436cef02934215d0b4ccfa2f compiler/typecheck/TcAnnotations.hs | 2 +- testsuite/tests/stage1/T13609.stderr | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcAnnotations.hs b/compiler/typecheck/TcAnnotations.hs index 43d2970..bdf6646 100644 --- a/compiler/typecheck/TcAnnotations.hs +++ b/compiler/typecheck/TcAnnotations.hs @@ -37,7 +37,7 @@ warnAnns :: [LAnnDecl Name] -> TcM [Annotation] warnAnns [] = return [] warnAnns anns@(L loc _ : _) = do { setSrcSpan loc $ addWarnTc NoReason $ - (text "Ignoring Ann annotation" <> plural anns <> comma + (text "Ignoring ANN annotation" <> plural anns <> comma <+> text "because this is a stage-1 compiler without -fexternal-interpreter or doesn't support GHCi") ; return [] } #else diff --git a/testsuite/tests/stage1/T13609.stderr b/testsuite/tests/stage1/T13609.stderr index 0a3c1cd..579f3e5 100644 --- a/testsuite/tests/stage1/T13609.stderr +++ b/testsuite/tests/stage1/T13609.stderr @@ -1,3 +1,3 @@ T13609.hs:3:1: warning: - Ignoring Ann annotation, because this is a stage-1 compiler without -fexternal-interpreter or doesn't support GHCi + Ignoring ANN annotation, because this is a stage-1 compiler without -fexternal-interpreter or doesn't support GHCi From git at git.haskell.org Mon May 1 15:15:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 May 2017 15:15:23 +0000 (UTC) Subject: [commit: ghc] master: Make LLVM output robust to -dead_strip on mach-o platforms (667abf1) Message-ID: <20170501151523.481593A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/667abf17dced8b4a4cd2dc6a291a6f244ffa031f/ghc >--------------------------------------------------------------- commit 667abf17dced8b4a4cd2dc6a291a6f244ffa031f Author: Moritz Angermann Date: Mon May 1 11:13:36 2017 -0400 Make LLVM output robust to -dead_strip on mach-o platforms This reverses commit 1686f30951292e94bf3076ce8b3eafb0bcbba91d (Mangle .subsections_via_symbols away., D3287), and implements proper support for `-dead_strip` via the injection of `.alt_entry` symbols for the function definition pointing to the beginning of the prefix data. This is the result of a lengthy discussion with rwbarton, and the following llvm-dev mailing list thread: http://lists.llvm.org/pipermail/llvm-dev/2017-March/110733.html The essential problem is that there is no reference from a function to its info table. This combined with `.subsections_via_symbols`, which llvm emits unconditionally, leads the linker to believe that the prefix data is unnecessary and stripping it away if presented with the `-dead_strip` flag. The NCG has for this purpose special $dsp (dead strip preventer) symbols and adds a relocation to the end of each function body pointing to that function's $dsp symbol. We cannot easily do the same thing via LLVM. Instead we use the `.alt_entry` directive on the function symbol, which causes the linker to treat it as a continuation of the previous symbol, namely the $dsp symbol. As a result the function body will not be separated from its info table. Reviewers: erikd, austin, rwbarton, bgamari Reviewed By: bgamari Subscribers: michalt, thomie Differential Revision: https://phabricator.haskell.org/D3290 >--------------------------------------------------------------- 667abf17dced8b4a4cd2dc6a291a6f244ffa031f compiler/llvmGen/LlvmCodeGen/Ppr.hs | 72 +++++++++++++++++++++++++++++++++++-- compiler/llvmGen/LlvmMangler.hs | 11 +----- 2 files changed, 71 insertions(+), 12 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Ppr.hs b/compiler/llvmGen/LlvmCodeGen/Ppr.hs index 37d1391..8b6340d 100644 --- a/compiler/llvmGen/LlvmCodeGen/Ppr.hs +++ b/compiler/llvmGen/LlvmCodeGen/Ppr.hs @@ -21,6 +21,7 @@ import FastString import Outputable import Unique +import DynFlags (targetPlatform) -- ---------------------------------------------------------------------------- -- * Top level @@ -150,8 +151,75 @@ pprLlvmCmmDecl (CmmProc mb_info entry_lbl live (ListGraph blks)) alias = LMGlobal funVar (Just $ LMBitc (LMStaticPointer defVar) (LMPointer $ LMInt 8)) - - return (ppLlvmGlobal alias $+$ ppLlvmFunction fun', []) + -- our beloved dead_strip preventer. + -- the idea here is to inject + -- + -- module asm "_symbol$dsp = _symbol-24" -- assuming prefix + -- of <{i64, i64, i64}> + -- module asm ".no_dead_strip _symbol$dsp" + -- + -- and thereby generating a second symbol + -- at the start of the info table, which is dead strip prevented. + -- + -- ideally, llvm should generate these for us, but as + -- things stand, this is the least hacky solution to + -- prevent dead_stripping of the prefix data, while + -- retaining dead stripping in general. + -- + -- The general layout of the above code results in the following: + -- + -- .------------. <- @$def$dsp + -- | Info Table | + -- |------------| <- @, @$def + -- | Fn Body | + -- '------------' + -- + -- Why this @ and @$def? As the textual llvm ir + -- generator is only handed typeless labes, it often does not + -- know the type of the label (e.g. function to call), until + -- the actual call happens. However, llvm requires symbol + -- lookups to be typed. Therfore we create the actual function + -- as @$def, and alias a bitcast to i8* as @. + -- Any subsequent lookup can lookup @ as i8* and + -- bitcast it to the required type once we want to call it. + -- + -- Why .no_dead_strip? Doesn't this prevent the linker from + -- -dead_strip'ing anything? Yes, it does. And we'll have to + -- live with this wart until a better solution is found that + -- ensures that all symbols that are used directly or + -- indirectly are marked used. + -- + -- This is all rather annoying. ghc 8.2 uses the infamous + -- Mangler to drop the .subsections_via_symbols directive + -- from the assembly. LLVM ingeniously emits said directive + -- unconditionally for mach-o files. To lift the need for + -- extra mangler step, we explicitly mark every symbol + -- .no_dead_strip. + -- + -- We are making a few assumptions here: + -- - the symbols end up being name _ in the final + -- assembly file. + -- + dsp <- case mb_info of + Nothing -> pure empty + Just (Statics _ statics) + | platformHasSubsectionsViaSymbols (targetPlatform dflags) -> do + infoStatics <- mapM genData statics + -- remember, the prefix_size is in bits! + let prefix_size = sum (map (llvmWidthInBits dflags . getStatType) + infoStatics) + dspName = defName `appendFS` fsLit "$dsp" + defSymbol = text "_" <> ftext defName + dspSymbol = text "_" <> ftext dspName + moduleAsm s = text "module asm" <+> doubleQuotes s + return $ text "; insert dead_strip preventer" + $+$ moduleAsm (dspSymbol <+> text "=" <+> defSymbol + <> text "-" <> int (prefix_size `div` 8)) + $+$ moduleAsm (text ".no_dead_strip" <+> dspSymbol) + $+$ text "; end dead_strip preventer" + | otherwise -> pure empty + + return (ppLlvmGlobal alias $+$ ppLlvmFunction fun' $+$ dsp, []) -- | The section we are putting info tables and their entry code into, should diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs index eed13ba..acf344f 100644 --- a/compiler/llvmGen/LlvmMangler.hs +++ b/compiler/llvmGen/LlvmMangler.hs @@ -47,20 +47,11 @@ type Rewrite = DynFlags -> B.ByteString -> Maybe B.ByteString -- | Rewrite a line of assembly source with the given rewrites, -- taking the first rewrite that applies. rewriteLine :: DynFlags -> [Rewrite] -> B.ByteString -> B.ByteString -rewriteLine dflags rewrites l - -- We disable .subsections_via_symbols on darwin and ios, as the llvm code - -- gen uses prefix data for the info table. This however does not prevent - -- llvm from generating .subsections_via_symbols, which in turn with - -- -dead_strip, strips the info tables, and therefore breaks ghc. - | isSubsectionsViaSymbols l = - (B.pack "## no .subsection_via_symbols for ghc. We need our info tables!") - | otherwise = +rewriteLine dflags rewrites l = case firstJust $ map (\rewrite -> rewrite dflags rest) rewrites of Nothing -> l Just rewritten -> B.concat $ [symbol, B.pack "\t", rewritten] where - isSubsectionsViaSymbols = B.isPrefixOf (B.pack ".subsections_via_symbols") - (symbol, rest) = splitLine l firstJust :: [Maybe a] -> Maybe a From git at git.haskell.org Mon May 1 16:24:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 May 2017 16:24:24 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: testsuite: Add test for #13609 (f8d909b) Message-ID: <20170501162424.9D1573A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/f8d909ba2ab9ccc89cf59a1097d78da8f82c793f/ghc >--------------------------------------------------------------- commit f8d909ba2ab9ccc89cf59a1097d78da8f82c793f Author: Ben Gamari Date: Sun Apr 30 23:19:26 2017 -0400 testsuite: Add test for #13609 (cherry picked from commit 18fbb9d32cbc157e3bbd235e392f1625f77321e3) >--------------------------------------------------------------- f8d909ba2ab9ccc89cf59a1097d78da8f82c793f testsuite/tests/stage1/T13609.hs | 5 +++++ testsuite/tests/stage1/T13609.stderr | 3 +++ testsuite/tests/stage1/all.T | 1 + 3 files changed, 9 insertions(+) diff --git a/testsuite/tests/stage1/T13609.hs b/testsuite/tests/stage1/T13609.hs new file mode 100644 index 0000000..e67eb32 --- /dev/null +++ b/testsuite/tests/stage1/T13609.hs @@ -0,0 +1,5 @@ +module M where + +{-# ANN myId "HLint: ignore" #-} +myId :: a -> a +myId x = x diff --git a/testsuite/tests/stage1/T13609.stderr b/testsuite/tests/stage1/T13609.stderr new file mode 100644 index 0000000..0a3c1cd --- /dev/null +++ b/testsuite/tests/stage1/T13609.stderr @@ -0,0 +1,3 @@ + +T13609.hs:3:1: warning: + Ignoring Ann annotation, because this is a stage-1 compiler without -fexternal-interpreter or doesn't support GHCi diff --git a/testsuite/tests/stage1/all.T b/testsuite/tests/stage1/all.T index a7f01b3..40bb274 100644 --- a/testsuite/tests/stage1/all.T +++ b/testsuite/tests/stage1/all.T @@ -4,3 +4,4 @@ setTestOpts(unless(config.stage == 1, skip)) # Test with stage1 compiler, see ticket:10382#comment:20. test('T2632', normal, compile, ['-XTemplateHaskellQuotes -package template-haskell']) +test('T13609', normal, compile, ['']) From git at git.haskell.org Mon May 1 16:24:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 May 2017 16:24:32 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump haddock submodule (f4841ad) Message-ID: <20170501162432.B2E2F3A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/f4841ad7c6c88251a9cd156888470d999b629b0f/ghc >--------------------------------------------------------------- commit f4841ad7c6c88251a9cd156888470d999b629b0f Author: Ben Gamari Date: Mon May 1 11:41:41 2017 -0400 Bump haddock submodule >--------------------------------------------------------------- f4841ad7c6c88251a9cd156888470d999b629b0f utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 0278700..2163981 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 02787004ffeb16c9d848b77b6e23598b58596348 +Subproject commit 2163981e773b76212b2265a1eb03208ee2e7edf2 From git at git.haskell.org Mon May 1 16:24:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 May 2017 16:24:27 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix capitalization in message for #13609 (110bcc0) Message-ID: <20170501162427.515853A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/110bcc0efe5bb669e8b635658ed18a603d6541a5/ghc >--------------------------------------------------------------- commit 110bcc0efe5bb669e8b635658ed18a603d6541a5 Author: Ben Gamari Date: Mon May 1 11:06:08 2017 -0400 Fix capitalization in message for #13609 I had meant to do this before merging but forgot. (cherry picked from commit c04bd55a8daaf254436cef02934215d0b4ccfa2f) >--------------------------------------------------------------- 110bcc0efe5bb669e8b635658ed18a603d6541a5 compiler/typecheck/TcAnnotations.hs | 2 +- testsuite/tests/stage1/T13609.stderr | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcAnnotations.hs b/compiler/typecheck/TcAnnotations.hs index 43d2970..bdf6646 100644 --- a/compiler/typecheck/TcAnnotations.hs +++ b/compiler/typecheck/TcAnnotations.hs @@ -37,7 +37,7 @@ warnAnns :: [LAnnDecl Name] -> TcM [Annotation] warnAnns [] = return [] warnAnns anns@(L loc _ : _) = do { setSrcSpan loc $ addWarnTc NoReason $ - (text "Ignoring Ann annotation" <> plural anns <> comma + (text "Ignoring ANN annotation" <> plural anns <> comma <+> text "because this is a stage-1 compiler without -fexternal-interpreter or doesn't support GHCi") ; return [] } #else diff --git a/testsuite/tests/stage1/T13609.stderr b/testsuite/tests/stage1/T13609.stderr index 0a3c1cd..579f3e5 100644 --- a/testsuite/tests/stage1/T13609.stderr +++ b/testsuite/tests/stage1/T13609.stderr @@ -1,3 +1,3 @@ T13609.hs:3:1: warning: - Ignoring Ann annotation, because this is a stage-1 compiler without -fexternal-interpreter or doesn't support GHCi + Ignoring ANN annotation, because this is a stage-1 compiler without -fexternal-interpreter or doesn't support GHCi From git at git.haskell.org Mon May 1 16:24:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 May 2017 16:24:30 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Ignore ANN pragmas with no TH and no external interpreter. (9446304) Message-ID: <20170501162430.05FC13A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/944630400117acdf2f97759b7ed8678e8d6cdf92/ghc >--------------------------------------------------------------- commit 944630400117acdf2f97759b7ed8678e8d6cdf92 Author: Shea Levy Date: Sun Apr 30 23:20:54 2017 -0400 Ignore ANN pragmas with no TH and no external interpreter. Reviewers: hvr, austin, bgamari, RyanGlScott Reviewed By: bgamari Subscribers: angerman, RyanGlScott, rwbarton, thomie GHC Trac Issues: #13609 Differential Revision: https://phabricator.haskell.org/D3496 (cherry picked from commit 7567b9ddba7c4304e8d0226e9bf82a054f37ce91) >--------------------------------------------------------------- 944630400117acdf2f97759b7ed8678e8d6cdf92 compiler/typecheck/TcAnnotations.hs | 25 ++++++++++++++++++++++++- 1 file changed, 24 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcAnnotations.hs b/compiler/typecheck/TcAnnotations.hs index 7b3cc65..43d2970 100644 --- a/compiler/typecheck/TcAnnotations.hs +++ b/compiler/typecheck/TcAnnotations.hs @@ -22,8 +22,31 @@ import TcRnMonad import SrcLoc import Outputable +-- Some platforms don't support the external interpreter, and +-- compilation on those platforms shouldn't fail just due to +-- annotations +#ifndef GHCI tcAnnotations :: [LAnnDecl Name] -> TcM [Annotation] -tcAnnotations anns = mapM tcAnnotation anns +tcAnnotations anns = do + dflags <- getDynFlags + case gopt Opt_ExternalInterpreter dflags of + True -> tcAnnotations' anns + False -> warnAnns anns +warnAnns :: [LAnnDecl Name] -> TcM [Annotation] +--- No GHCI; emit a warning (not an error) and ignore. cf Trac #4268 +warnAnns [] = return [] +warnAnns anns@(L loc _ : _) + = do { setSrcSpan loc $ addWarnTc NoReason $ + (text "Ignoring Ann annotation" <> plural anns <> comma + <+> text "because this is a stage-1 compiler without -fexternal-interpreter or doesn't support GHCi") + ; return [] } +#else +tcAnnotations :: [LAnnDecl Name] -> TcM [Annotation] +tcAnnotations = tcAnnotations' +#endif + +tcAnnotations' :: [LAnnDecl Name] -> TcM [Annotation] +tcAnnotations' anns = mapM tcAnnotation anns tcAnnotation :: LAnnDecl Name -> TcM Annotation tcAnnotation (L loc ann@(HsAnnotation _ provenance expr)) = do From git at git.haskell.org Mon May 1 16:29:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 May 2017 16:29:40 +0000 (UTC) Subject: [commit: ghc] master: PPC NCG: Lower MO_*_Fabs as PowerPC fabs instruction (068af01) Message-ID: <20170501162940.954AF3A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/068af0162a47b1fd7809d056ccc2d80e480d53f5/ghc >--------------------------------------------------------------- commit 068af0162a47b1fd7809d056ccc2d80e480d53f5 Author: Peter Trommler Date: Mon May 1 11:17:25 2017 -0400 PPC NCG: Lower MO_*_Fabs as PowerPC fabs instruction In Phab:D3265 we introduced MO_F32_Fabs and MO_F64_Fabs. This patch improves code generation by generating PowerPC fabs instructions. Test Plan: run numeric/should_run/numrun015 or validate Reviewers: austin, bgamari, hvr, simonmar, erikd Reviewed By: erikd Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3512 >--------------------------------------------------------------- 068af0162a47b1fd7809d056ccc2d80e480d53f5 compiler/codeGen/StgCmmPrim.hs | 6 ++++-- compiler/nativeGen/PPC/CodeGen.hs | 8 ++++++++ compiler/nativeGen/PPC/Instr.hs | 3 +++ compiler/nativeGen/PPC/Ppr.hs | 1 + 4 files changed, 16 insertions(+), 2 deletions(-) diff --git a/compiler/codeGen/StgCmmPrim.hs b/compiler/codeGen/StgCmmPrim.hs index 235109f..e0a68f6 100644 --- a/compiler/codeGen/StgCmmPrim.hs +++ b/compiler/codeGen/StgCmmPrim.hs @@ -852,10 +852,12 @@ callishPrimOpSupported dflags op || ppc) || llvm -> Left (MO_U_Mul2 (wordWidth dflags)) | otherwise -> Right genericWordMul2Op - FloatFabsOp | (ncg && x86ish) + FloatFabsOp | (ncg && x86ish + || ppc) || llvm -> Left MO_F32_Fabs | otherwise -> Right $ genericFabsOp W32 - DoubleFabsOp | (ncg && x86ish) + DoubleFabsOp | (ncg && x86ish + || ppc) || llvm -> Left MO_F64_Fabs | otherwise -> Right $ genericFabsOp W64 diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs index 1467267..a1a205b 100644 --- a/compiler/nativeGen/PPC/CodeGen.hs +++ b/compiler/nativeGen/PPC/CodeGen.hs @@ -1233,6 +1233,8 @@ genCCall target dest_regs argsAndHints dest_regs argsAndHints PrimTarget (MO_SubIntC width) -> addSubCOp SUBFO platform width dest_regs argsAndHints + PrimTarget MO_F64_Fabs -> fabs platform dest_regs argsAndHints + PrimTarget MO_F32_Fabs -> fabs platform dest_regs argsAndHints _ -> genCCall' dflags (platformToGCP platform) target dest_regs argsAndHints where divOp1 platform signed width [res_q, res_r] [arg_x, arg_y] @@ -1444,6 +1446,12 @@ genCCall target dest_regs argsAndHints ] addSubCOp _ _ _ _ _ = panic "genCall: Wrong number of arguments/results for addC" + fabs platform [res] [arg] + = do let res_r = getRegisterReg platform (CmmLocal res) + (arg_reg, arg_code) <- getSomeReg arg + return $ arg_code `snocOL` FABS res_r arg_reg + fabs _ _ _ + = panic "genCall: Wrong number of arguments/results for fabs" -- TODO: replace 'Int' by an enum such as 'PPC_64ABI' data GenCCallPlatform = GCPLinux | GCPDarwin | GCPLinux64ELF !Int | GCPAIX diff --git a/compiler/nativeGen/PPC/Instr.hs b/compiler/nativeGen/PPC/Instr.hs index e395b38..b8b5043 100644 --- a/compiler/nativeGen/PPC/Instr.hs +++ b/compiler/nativeGen/PPC/Instr.hs @@ -254,6 +254,7 @@ data Instr | FSUB Format Reg Reg Reg | FMUL Format Reg Reg Reg | FDIV Format Reg Reg Reg + | FABS Reg Reg -- abs is the same for single and double | FNEG Reg Reg -- negate is the same for single and double prec. | FCMP Reg Reg @@ -342,6 +343,7 @@ ppc_regUsageOfInstr platform instr FSUB _ r1 r2 r3 -> usage ([r2,r3], [r1]) FMUL _ r1 r2 r3 -> usage ([r2,r3], [r1]) FDIV _ r1 r2 r3 -> usage ([r2,r3], [r1]) + FABS r1 r2 -> usage ([r2], [r1]) FNEG r1 r2 -> usage ([r2], [r1]) FCMP r1 r2 -> usage ([r1,r2], []) FCTIWZ r1 r2 -> usage ([r2], [r1]) @@ -436,6 +438,7 @@ ppc_patchRegsOfInstr instr env FSUB fmt r1 r2 r3 -> FSUB fmt (env r1) (env r2) (env r3) FMUL fmt r1 r2 r3 -> FMUL fmt (env r1) (env r2) (env r3) FDIV fmt r1 r2 r3 -> FDIV fmt (env r1) (env r2) (env r3) + FABS r1 r2 -> FABS (env r1) (env r2) FNEG r1 r2 -> FNEG (env r1) (env r2) FCMP r1 r2 -> FCMP (env r1) (env r2) FCTIWZ r1 r2 -> FCTIWZ (env r1) (env r2) diff --git a/compiler/nativeGen/PPC/Ppr.hs b/compiler/nativeGen/PPC/Ppr.hs index 025dfaf..7f30c5b 100644 --- a/compiler/nativeGen/PPC/Ppr.hs +++ b/compiler/nativeGen/PPC/Ppr.hs @@ -870,6 +870,7 @@ pprInstr (FADD fmt reg1 reg2 reg3) = pprBinaryF (sLit "fadd") fmt reg1 reg2 reg3 pprInstr (FSUB fmt reg1 reg2 reg3) = pprBinaryF (sLit "fsub") fmt reg1 reg2 reg3 pprInstr (FMUL fmt reg1 reg2 reg3) = pprBinaryF (sLit "fmul") fmt reg1 reg2 reg3 pprInstr (FDIV fmt reg1 reg2 reg3) = pprBinaryF (sLit "fdiv") fmt reg1 reg2 reg3 +pprInstr (FABS reg1 reg2) = pprUnary (sLit "fabs") reg1 reg2 pprInstr (FNEG reg1 reg2) = pprUnary (sLit "fneg") reg1 reg2 pprInstr (FCMP reg1 reg2) = hcat [ From git at git.haskell.org Mon May 1 16:29:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 May 2017 16:29:46 +0000 (UTC) Subject: [commit: ghc] master: [linker] Add ocInit/ocDeinit for ELF (e250178) Message-ID: <20170501162946.1CA943A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e25017819b58efd0a4c45796fa8ab8af6cc5db93/ghc >--------------------------------------------------------------- commit e25017819b58efd0a4c45796fa8ab8af6cc5db93 Author: Moritz Angermann Date: Mon May 1 11:18:14 2017 -0400 [linker] Add ocInit/ocDeinit for ELF This fills out the extended `info` structs, and will be subsequently used in the arm and arm64 linker for elf. Depends on: D3446, D3459 Reviewers: bgamari, austin, erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3447 >--------------------------------------------------------------- e25017819b58efd0a4c45796fa8ab8af6cc5db93 rts/Linker.c | 56 +++++++++++----- rts/linker/Elf.c | 166 +++++++++++++++++++++++++++++++++++++++++++++-- rts/linker/Elf.h | 4 ++ rts/linker/LoadArchive.c | 5 ++ 4 files changed, 209 insertions(+), 22 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 e25017819b58efd0a4c45796fa8ab8af6cc5db93 From git at git.haskell.org Mon May 1 16:29:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 May 2017 16:29:43 +0000 (UTC) Subject: [commit: ghc] master: Avoid excessive space usage from unfoldings in CoreTidy (5c602d2) Message-ID: <20170501162943.54E523A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5c602d2228d28530621cc6c94fbb736b13f474fb/ghc >--------------------------------------------------------------- commit 5c602d2228d28530621cc6c94fbb736b13f474fb Author: Reid Barton Date: Mon May 1 11:17:47 2017 -0400 Avoid excessive space usage from unfoldings in CoreTidy Test Plan: validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie GHC Trac Issues: #13564 Differential Revision: https://phabricator.haskell.org/D3516 >--------------------------------------------------------------- 5c602d2228d28530621cc6c94fbb736b13f474fb compiler/coreSyn/CoreTidy.hs | 8 +++++++- compiler/main/TidyPgm.hs | 5 ++++- testsuite/tests/perf/compiler/all.T | 12 ++++++++---- 3 files changed, 19 insertions(+), 6 deletions(-) diff --git a/compiler/coreSyn/CoreTidy.hs b/compiler/coreSyn/CoreTidy.hs index 7f82bec..89ce692 100644 --- a/compiler/coreSyn/CoreTidy.hs +++ b/compiler/coreSyn/CoreTidy.hs @@ -15,6 +15,7 @@ module CoreTidy ( #include "HsVersions.h" import CoreSyn +import CoreSeq ( seqUnfolding ) import CoreArity import Id import IdInfo @@ -223,9 +224,14 @@ tidyUnfolding tidy_env unf@(CoreUnfolding { uf_tmpl = unf_rhs, uf_src = src }) unf_from_rhs | isStableSource src - = unf { uf_tmpl = tidyExpr tidy_env unf_rhs } -- Preserves OccInfo + = seqIt $ unf { uf_tmpl = tidyExpr tidy_env unf_rhs } -- Preserves OccInfo + -- This seqIt avoids a space leak: otherwise the uf_is_value, + -- uf_is_conlike, ... fields may retain a reference to the + -- pre-tidied expression forever (ToIface doesn't look at them) + | otherwise = unf_from_rhs + where seqIt unf = seqUnfolding unf `seq` unf tidyUnfolding _ unf _ = unf -- NoUnfolding or OtherCon {- diff --git a/compiler/main/TidyPgm.hs b/compiler/main/TidyPgm.hs index 21d0208..4b9fbae 100644 --- a/compiler/main/TidyPgm.hs +++ b/compiler/main/TidyPgm.hs @@ -22,6 +22,7 @@ import CoreMonad import CorePrep import CoreUtils (rhsIsStatic) import CoreStats (coreBindsStats, CoreStats(..)) +import CoreSeq (seqBinds) import CoreLint import Literal import Rules @@ -1134,7 +1135,9 @@ tidyTopBinds hsc_env this_mod unfold_env init_occ_env binds = do mkIntegerId <- lookupMkIntegerName dflags hsc_env integerSDataCon <- lookupIntegerSDataConName dflags hsc_env let cvt_integer = cvtLitInteger dflags mkIntegerId integerSDataCon - return $ tidy cvt_integer init_env binds + result = tidy cvt_integer init_env binds + seqBinds (snd result) `seq` return result + -- This seqBinds avoids a spike in space usage (see #13564) where dflags = hsc_dflags hsc_env diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 3acc511..733e3ba 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -742,7 +742,7 @@ test('T9020', test('T9675', [ only_ways(['optasm']), compiler_stats_num_field('max_bytes_used', # Note [residency] - [(wordsize(64), 29871032, 15), + [(wordsize(64), 17675240, 15), # 2014-10-13 29596552 # 2014-10-13 26570896 seq the DmdEnv in seqDmdType as well # 2014-10-13 18582472 different machines giving different results.. @@ -752,12 +752,13 @@ test('T9675', # 2015-12-11 30837312 TypeInType (see #11196) # 2016-03-14 38776008 Final demand analyzer run # 2016-04-01 29871032 Fix leaks in demand analysis + # 2016-04-30 17675240 Fix leaks in tidy unfoldings (wordsize(32), 18043224, 15) # 2015-07-11 15341228 (x86/Linux, 64-bit machine) use +RTS -G1 # 2016-04-06 18043224 (x86/Linux, 64-bit machine) ]), compiler_stats_num_field('peak_megabytes_allocated', # Note [residency] - [(wordsize(64), 121, 15), + [(wordsize(64), 63, 15), # 2014-10-13 66 # 2014-10-13 58 seq the DmdEnv in seqDmdType as well # 2014-10-13 49 different machines giving different results... @@ -768,6 +769,7 @@ test('T9675', # 2015-12-11 113 TypeInType (see #11196) # 2016-04-14 144 Final demand analyzer run # 2016-07-26 121 Unboxed sums? + # 2017-04-30 63 Fix leaks in tidy unfoldings (wordsize(32), 56, 15) # 2015-07-11 56 (x86/Linux, 64-bit machine) use +RTS -G1 ]), @@ -933,7 +935,7 @@ test('T9233', test('T10370', [ only_ways(['optasm']), compiler_stats_num_field('max_bytes_used', # Note [residency] - [(wordsize(64), 41291976, 15), + [(wordsize(64), 31524048, 15), # 2015-10-22 19548720 # 2016-02-24 22823976 Changing Levity to RuntimeRep; not sure why this regresses though, even after some analysis # 2016-04-14 28256896 final demand analyzer run @@ -949,19 +951,21 @@ test('T10370', # 2017-02-17 51126304 Type-indexed Typeable # 2017-02-27 43455848 Likely drift from recent simplifier improvements # 2017-02-25 41291976 Early inline patch + # 2017-04-30 31524048 Fix leaks in tidy unfoldings (wordsize(32), 19276304, 15), # 2015-10-22 11371496 # 2017-03-24 19276304 (x86/Linux, 64-bit machine) ]), compiler_stats_num_field('peak_megabytes_allocated', # Note [residency] - [(wordsize(64), 154, 15), + [(wordsize(64), 117, 15), # 2015-10-22 76 # 2016-04-14 101 final demand analyzer run # 2016-08-08 121 see above # 2017-01-18 146 Allow top-level string literals in Core # 2017-02-17 187 Type-indexed Typeable # 2017-02-25 154 Early inline patch + # 2017-04-30 117 Fix leaks in tidy unfoldings (wordsize(32), 69, 15), # 2015-10-22 39 # 2017-03-24 69 From git at git.haskell.org Mon May 1 16:58:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 May 2017 16:58:53 +0000 (UTC) Subject: [commit: packages/array] master: Export unsafeFreezeIOUArray (f7b69e9) Message-ID: <20170501165853.416413A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array On branch : master Link : http://git.haskell.org/packages/array.git/commitdiff/f7b69e9cb914cb69bbede5264729523fb8669db1 >--------------------------------------------------------------- commit f7b69e9cb914cb69bbede5264729523fb8669db1 Author: Ben Gamari Date: Mon May 1 12:57:25 2017 -0400 Export unsafeFreezeIOUArray The fact that this was previously hidden appears to be an oversight and I've needed it at least once. >--------------------------------------------------------------- f7b69e9cb914cb69bbede5264729523fb8669db1 Data/Array/IO/Internals.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/Data/Array/IO/Internals.hs b/Data/Array/IO/Internals.hs index 4f784de..c9738e9 100644 --- a/Data/Array/IO/Internals.hs +++ b/Data/Array/IO/Internals.hs @@ -22,6 +22,7 @@ module Data.Array.IO.Internals ( IOUArray(..), -- instance of: Eq, Typeable castIOUArray, -- :: IOUArray ix a -> IO (IOUArray ix b) unsafeThawIOUArray, + unsafeFreezeIOUArray ) where import Data.Int From git at git.haskell.org Tue May 2 02:31:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 May 2017 02:31:11 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Avoid excessive space usage from unfoldings in CoreTidy (fc2236e) Message-ID: <20170502023111.7339E3A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/fc2236e8db7550287e764d90410a002b02c55180/ghc >--------------------------------------------------------------- commit fc2236e8db7550287e764d90410a002b02c55180 Author: Reid Barton Date: Mon May 1 11:17:47 2017 -0400 Avoid excessive space usage from unfoldings in CoreTidy Test Plan: validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie GHC Trac Issues: #13564 Differential Revision: https://phabricator.haskell.org/D3516 (cherry picked from commit 5c602d2228d28530621cc6c94fbb736b13f474fb) >--------------------------------------------------------------- fc2236e8db7550287e764d90410a002b02c55180 compiler/coreSyn/CoreTidy.hs | 8 +++++++- compiler/main/TidyPgm.hs | 5 ++++- testsuite/tests/perf/compiler/all.T | 12 ++++++++---- 3 files changed, 19 insertions(+), 6 deletions(-) diff --git a/compiler/coreSyn/CoreTidy.hs b/compiler/coreSyn/CoreTidy.hs index 7f82bec..89ce692 100644 --- a/compiler/coreSyn/CoreTidy.hs +++ b/compiler/coreSyn/CoreTidy.hs @@ -15,6 +15,7 @@ module CoreTidy ( #include "HsVersions.h" import CoreSyn +import CoreSeq ( seqUnfolding ) import CoreArity import Id import IdInfo @@ -223,9 +224,14 @@ tidyUnfolding tidy_env unf@(CoreUnfolding { uf_tmpl = unf_rhs, uf_src = src }) unf_from_rhs | isStableSource src - = unf { uf_tmpl = tidyExpr tidy_env unf_rhs } -- Preserves OccInfo + = seqIt $ unf { uf_tmpl = tidyExpr tidy_env unf_rhs } -- Preserves OccInfo + -- This seqIt avoids a space leak: otherwise the uf_is_value, + -- uf_is_conlike, ... fields may retain a reference to the + -- pre-tidied expression forever (ToIface doesn't look at them) + | otherwise = unf_from_rhs + where seqIt unf = seqUnfolding unf `seq` unf tidyUnfolding _ unf _ = unf -- NoUnfolding or OtherCon {- diff --git a/compiler/main/TidyPgm.hs b/compiler/main/TidyPgm.hs index 21d0208..4b9fbae 100644 --- a/compiler/main/TidyPgm.hs +++ b/compiler/main/TidyPgm.hs @@ -22,6 +22,7 @@ import CoreMonad import CorePrep import CoreUtils (rhsIsStatic) import CoreStats (coreBindsStats, CoreStats(..)) +import CoreSeq (seqBinds) import CoreLint import Literal import Rules @@ -1134,7 +1135,9 @@ tidyTopBinds hsc_env this_mod unfold_env init_occ_env binds = do mkIntegerId <- lookupMkIntegerName dflags hsc_env integerSDataCon <- lookupIntegerSDataConName dflags hsc_env let cvt_integer = cvtLitInteger dflags mkIntegerId integerSDataCon - return $ tidy cvt_integer init_env binds + result = tidy cvt_integer init_env binds + seqBinds (snd result) `seq` return result + -- This seqBinds avoids a spike in space usage (see #13564) where dflags = hsc_dflags hsc_env diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 6017434..f8dbdd5 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -740,7 +740,7 @@ test('T9020', test('T9675', [ only_ways(['optasm']), compiler_stats_num_field('max_bytes_used', # Note [residency] - [(wordsize(64), 29871032, 15), + [(wordsize(64), 17675240, 15), # 2014-10-13 29596552 # 2014-10-13 26570896 seq the DmdEnv in seqDmdType as well # 2014-10-13 18582472 different machines giving different results.. @@ -750,12 +750,13 @@ test('T9675', # 2015-12-11 30837312 TypeInType (see #11196) # 2016-03-14 38776008 Final demand analyzer run # 2016-04-01 29871032 Fix leaks in demand analysis + # 2016-04-30 17675240 Fix leaks in tidy unfoldings (wordsize(32), 18043224, 15) # 2015-07-11 15341228 (x86/Linux, 64-bit machine) use +RTS -G1 # 2016-04-06 18043224 (x86/Linux, 64-bit machine) ]), compiler_stats_num_field('peak_megabytes_allocated', # Note [residency] - [(wordsize(64), 121, 15), + [(wordsize(64), 63, 15), # 2014-10-13 66 # 2014-10-13 58 seq the DmdEnv in seqDmdType as well # 2014-10-13 49 different machines giving different results... @@ -766,6 +767,7 @@ test('T9675', # 2015-12-11 113 TypeInType (see #11196) # 2016-04-14 144 Final demand analyzer run # 2016-07-26 121 Unboxed sums? + # 2017-04-30 63 Fix leaks in tidy unfoldings (wordsize(32), 56, 15) # 2015-07-11 56 (x86/Linux, 64-bit machine) use +RTS -G1 ]), @@ -931,7 +933,7 @@ test('T9233', test('T10370', [ only_ways(['optasm']), compiler_stats_num_field('max_bytes_used', # Note [residency] - [(wordsize(64), 41291976, 15), + [(wordsize(64), 31524048, 15), # 2015-10-22 19548720 # 2016-02-24 22823976 Changing Levity to RuntimeRep; not sure why this regresses though, even after some analysis # 2016-04-14 28256896 final demand analyzer run @@ -947,19 +949,21 @@ test('T10370', # 2017-02-17 51126304 Type-indexed Typeable # 2017-02-27 43455848 Likely drift from recent simplifier improvements # 2017-02-25 41291976 Early inline patch + # 2017-04-30 31524048 Fix leaks in tidy unfoldings (wordsize(32), 19276304, 15), # 2015-10-22 11371496 # 2017-03-24 19276304 (x86/Linux, 64-bit machine) ]), compiler_stats_num_field('peak_megabytes_allocated', # Note [residency] - [(wordsize(64), 154, 15), + [(wordsize(64), 117, 15), # 2015-10-22 76 # 2016-04-14 101 final demand analyzer run # 2016-08-08 121 see above # 2017-01-18 146 Allow top-level string literals in Core # 2017-02-17 187 Type-indexed Typeable # 2017-02-25 154 Early inline patch + # 2017-04-30 117 Fix leaks in tidy unfoldings (wordsize(32), 69, 15), # 2015-10-22 39 # 2017-03-24 69 From git at git.haskell.org Tue May 2 02:31:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 May 2017 02:31:14 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: PPC NCG: Lower MO_*_Fabs as PowerPC fabs instruction (bd9295d) Message-ID: <20170502023114.3294D3A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/bd9295d0b44897fd74c846e011ad07d9612661c1/ghc >--------------------------------------------------------------- commit bd9295d0b44897fd74c846e011ad07d9612661c1 Author: Peter Trommler Date: Mon May 1 11:17:25 2017 -0400 PPC NCG: Lower MO_*_Fabs as PowerPC fabs instruction In Phab:D3265 we introduced MO_F32_Fabs and MO_F64_Fabs. This patch improves code generation by generating PowerPC fabs instructions. Test Plan: run numeric/should_run/numrun015 or validate Reviewers: austin, bgamari, hvr, simonmar, erikd Reviewed By: erikd Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3512 (cherry picked from commit 068af0162a47b1fd7809d056ccc2d80e480d53f5) >--------------------------------------------------------------- bd9295d0b44897fd74c846e011ad07d9612661c1 compiler/codeGen/StgCmmPrim.hs | 6 ++++-- compiler/nativeGen/PPC/CodeGen.hs | 8 ++++++++ compiler/nativeGen/PPC/Instr.hs | 3 +++ compiler/nativeGen/PPC/Ppr.hs | 1 + 4 files changed, 16 insertions(+), 2 deletions(-) diff --git a/compiler/codeGen/StgCmmPrim.hs b/compiler/codeGen/StgCmmPrim.hs index 235109f..e0a68f6 100644 --- a/compiler/codeGen/StgCmmPrim.hs +++ b/compiler/codeGen/StgCmmPrim.hs @@ -852,10 +852,12 @@ callishPrimOpSupported dflags op || ppc) || llvm -> Left (MO_U_Mul2 (wordWidth dflags)) | otherwise -> Right genericWordMul2Op - FloatFabsOp | (ncg && x86ish) + FloatFabsOp | (ncg && x86ish + || ppc) || llvm -> Left MO_F32_Fabs | otherwise -> Right $ genericFabsOp W32 - DoubleFabsOp | (ncg && x86ish) + DoubleFabsOp | (ncg && x86ish + || ppc) || llvm -> Left MO_F64_Fabs | otherwise -> Right $ genericFabsOp W64 diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs index 1467267..a1a205b 100644 --- a/compiler/nativeGen/PPC/CodeGen.hs +++ b/compiler/nativeGen/PPC/CodeGen.hs @@ -1233,6 +1233,8 @@ genCCall target dest_regs argsAndHints dest_regs argsAndHints PrimTarget (MO_SubIntC width) -> addSubCOp SUBFO platform width dest_regs argsAndHints + PrimTarget MO_F64_Fabs -> fabs platform dest_regs argsAndHints + PrimTarget MO_F32_Fabs -> fabs platform dest_regs argsAndHints _ -> genCCall' dflags (platformToGCP platform) target dest_regs argsAndHints where divOp1 platform signed width [res_q, res_r] [arg_x, arg_y] @@ -1444,6 +1446,12 @@ genCCall target dest_regs argsAndHints ] addSubCOp _ _ _ _ _ = panic "genCall: Wrong number of arguments/results for addC" + fabs platform [res] [arg] + = do let res_r = getRegisterReg platform (CmmLocal res) + (arg_reg, arg_code) <- getSomeReg arg + return $ arg_code `snocOL` FABS res_r arg_reg + fabs _ _ _ + = panic "genCall: Wrong number of arguments/results for fabs" -- TODO: replace 'Int' by an enum such as 'PPC_64ABI' data GenCCallPlatform = GCPLinux | GCPDarwin | GCPLinux64ELF !Int | GCPAIX diff --git a/compiler/nativeGen/PPC/Instr.hs b/compiler/nativeGen/PPC/Instr.hs index e395b38..b8b5043 100644 --- a/compiler/nativeGen/PPC/Instr.hs +++ b/compiler/nativeGen/PPC/Instr.hs @@ -254,6 +254,7 @@ data Instr | FSUB Format Reg Reg Reg | FMUL Format Reg Reg Reg | FDIV Format Reg Reg Reg + | FABS Reg Reg -- abs is the same for single and double | FNEG Reg Reg -- negate is the same for single and double prec. | FCMP Reg Reg @@ -342,6 +343,7 @@ ppc_regUsageOfInstr platform instr FSUB _ r1 r2 r3 -> usage ([r2,r3], [r1]) FMUL _ r1 r2 r3 -> usage ([r2,r3], [r1]) FDIV _ r1 r2 r3 -> usage ([r2,r3], [r1]) + FABS r1 r2 -> usage ([r2], [r1]) FNEG r1 r2 -> usage ([r2], [r1]) FCMP r1 r2 -> usage ([r1,r2], []) FCTIWZ r1 r2 -> usage ([r2], [r1]) @@ -436,6 +438,7 @@ ppc_patchRegsOfInstr instr env FSUB fmt r1 r2 r3 -> FSUB fmt (env r1) (env r2) (env r3) FMUL fmt r1 r2 r3 -> FMUL fmt (env r1) (env r2) (env r3) FDIV fmt r1 r2 r3 -> FDIV fmt (env r1) (env r2) (env r3) + FABS r1 r2 -> FABS (env r1) (env r2) FNEG r1 r2 -> FNEG (env r1) (env r2) FCMP r1 r2 -> FCMP (env r1) (env r2) FCTIWZ r1 r2 -> FCTIWZ (env r1) (env r2) diff --git a/compiler/nativeGen/PPC/Ppr.hs b/compiler/nativeGen/PPC/Ppr.hs index 025dfaf..7f30c5b 100644 --- a/compiler/nativeGen/PPC/Ppr.hs +++ b/compiler/nativeGen/PPC/Ppr.hs @@ -870,6 +870,7 @@ pprInstr (FADD fmt reg1 reg2 reg3) = pprBinaryF (sLit "fadd") fmt reg1 reg2 reg3 pprInstr (FSUB fmt reg1 reg2 reg3) = pprBinaryF (sLit "fsub") fmt reg1 reg2 reg3 pprInstr (FMUL fmt reg1 reg2 reg3) = pprBinaryF (sLit "fmul") fmt reg1 reg2 reg3 pprInstr (FDIV fmt reg1 reg2 reg3) = pprBinaryF (sLit "fdiv") fmt reg1 reg2 reg3 +pprInstr (FABS reg1 reg2) = pprUnary (sLit "fabs") reg1 reg2 pprInstr (FNEG reg1 reg2) = pprUnary (sLit "fneg") reg1 reg2 pprInstr (FCMP reg1 reg2) = hcat [ From git at git.haskell.org Tue May 2 02:31:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 May 2017 02:31:16 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump haddock submodule (3e25336) Message-ID: <20170502023116.E26FA3A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/3e25336f49e88bb2d97f5e763c537631a4fe375c/ghc >--------------------------------------------------------------- commit 3e25336f49e88bb2d97f5e763c537631a4fe375c Author: Ben Gamari Date: Mon May 1 20:44:42 2017 -0400 Bump haddock submodule Fixes previously buggy commit >--------------------------------------------------------------- 3e25336f49e88bb2d97f5e763c537631a4fe375c utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 2163981..e0e6615 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 2163981e773b76212b2265a1eb03208ee2e7edf2 +Subproject commit e0e6615dd421f1b332ce2b11a98de768fa7c29a8 From git at git.haskell.org Tue May 2 03:05:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 May 2017 03:05:09 +0000 (UTC) Subject: [commit: ghc] master: Bump array submodule (f2c35d7) Message-ID: <20170502030509.F0B013A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f2c35d7cb5374c8f92459396cd623e1319217e33/ghc >--------------------------------------------------------------- commit f2c35d7cb5374c8f92459396cd623e1319217e33 Author: Ben Gamari Date: Mon May 1 12:59:36 2017 -0400 Bump array submodule >--------------------------------------------------------------- f2c35d7cb5374c8f92459396cd623e1319217e33 libraries/array | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/array b/libraries/array index db07d53..f7b69e9 160000 --- a/libraries/array +++ b/libraries/array @@ -1 +1 @@ -Subproject commit db07d534feb267d5f81e1301f6a0cb726c4c2ea2 +Subproject commit f7b69e9cb914cb69bbede5264729523fb8669db1 From git at git.haskell.org Tue May 2 03:05:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 May 2017 03:05:12 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Bump allocations of T3064 (3746f62) Message-ID: <20170502030512.A831A3A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3746f623b3939ae81a0d5bf99d9758eb8bfcb7b0/ghc >--------------------------------------------------------------- commit 3746f623b3939ae81a0d5bf99d9758eb8bfcb7b0 Author: Ben Gamari Date: Mon May 1 20:42:38 2017 -0400 testsuite: Bump allocations of T3064 This seems to have regressed due to, commit 5c602d2228d28530621cc6c94fbb736b13f474fb Author: Reid Barton Date: Mon May 1 11:17:47 2017 -0400 Avoid excessive space usage from unfoldings in CoreTidy >--------------------------------------------------------------- 3746f623b3939ae81a0d5bf99d9758eb8bfcb7b0 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 733e3ba..361f533 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -330,7 +330,7 @@ test('T3064', # 2016-04-06: 153261024 (x86/Linux) probably wildcard refactor # 2017-03-24: 134044092 (x86/Linux, 64-bit machine) Update - (wordsize(64), 265950920, 5)]), + (wordsize(64), 281509496, 5)]), # (amd64/Linux) (2011-06-28): 73259544 # (amd64/Linux) (2013-02-07): 224798696 # (amd64/Linux) (2013-08-02): 236404384, increase from roles @@ -356,6 +356,7 @@ test('T3064', # (amd64/Darwin) (2017-01-23): 306222424 Presumably creep from recent changes (Typeable?) # (amd64/Linux) (2017-02-14): 259815560 Early inline patch: 9% improvement # (amd64/Linux) (2017-03-31): 265950920 Fix memory leak in simplifier + # (amd64/Linux) (2017-05-01): 281509496 Avoid excessive space usage from unfoldings in CoreTidy ################################### # deactivated for now, as this metric became too volatile recently From git at git.haskell.org Tue May 2 09:14:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 May 2017 09:14:28 +0000 (UTC) Subject: [commit: ghc] master: Improve SpecConstr when there are many opportunities (c46a600) Message-ID: <20170502091428.C94E63A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c46a600f320b25e0ac73107acdb12a33d7fbd9c3/ghc >--------------------------------------------------------------- commit c46a600f320b25e0ac73107acdb12a33d7fbd9c3 Author: Simon Peyton Jones Date: Thu Apr 27 11:15:00 2017 +0100 Improve SpecConstr when there are many opportunities SpecConstr has -fspec-contr-count=N which limits the maximum number of specialisations we make for any particular function. But until now, if that limit was exceeded we discarded all the candidates! So adding a new specialisaiton opportunity (by adding a new call site, or improving the optimiser) could result in less specialisation and worse performance. This patch instead picks the top N candidates, resulting in less brittle behaviour. See Note [Choosing patterns]. >--------------------------------------------------------------- c46a600f320b25e0ac73107acdb12a33d7fbd9c3 compiler/specialise/SpecConstr.hs | 156 +++++++++++++++++++++++++++----------- 1 file changed, 113 insertions(+), 43 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 c46a600f320b25e0ac73107acdb12a33d7fbd9c3 From git at git.haskell.org Tue May 2 09:14:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 May 2017 09:14:31 +0000 (UTC) Subject: [commit: ghc] master: Fix a small Float-Out bug (ff23978) Message-ID: <20170502091431.8370B3A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ff239787f7170a93f1015bd0f5582772b7b87f0a/ghc >--------------------------------------------------------------- commit ff239787f7170a93f1015bd0f5582772b7b87f0a Author: Simon Peyton Jones Date: Wed Apr 26 17:43:24 2017 +0100 Fix a small Float-Out bug The float-out pass uses a heuristic based on strictness info. But it was getting the strictness info mis-aligned; I'd forgotten that strictness flags only apply to /value/ arguments. This patch fixes it. It has some surprising effects! -------------------------------------------------------------------------------- Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- integer -0.1% +9.9% +0.2% +0.2% +0.0% lcss +0.0% +0.0% -11.9% -11.9% +0.0% queens -0.2% +29.0% 0.02 0.02 +0.0% simple -0.1% -22.6% -21.7% -21.7% -3.6% treejoin +0.0% +0.0% -12.3% -12.6% +0.0% -------------------------------------------------------------------------------- Min -0.2% -22.6% -21.7% -21.7% -10.0% Max +3.3% +29.0% +19.2% +19.2% +50.0% Geometric Mean +0.0% +0.1% -2.1% -2.1% +0.2% The 'queens' and 'integer' allocation regressions are because, just before let-floatting, we get \v -> foldr k z (case x of I# y -> build ..y..) Becase of Note [Case MFEs] we don't float the build; so fusion happens. This increases allocation in queens because the build isn't shared; but actaully runtime improves solidly. Situation is similar in integer, although I think runtime gets a bit worse. The bug meant that, because of foldr's type arguments, the mis-aligned strictness info meant that the entire (case x ...) was floated, so fusion failed, but sharing happened. This is all very artificial-benchmark-ish so I'm not losing sleep over it. I did see some runtime numbers increasd, but I think it's noise; the differnce went away when I tried them one by one afterwards. >--------------------------------------------------------------- ff239787f7170a93f1015bd0f5582772b7b87f0a compiler/simplCore/SetLevels.hs | 39 +++++++++++++++++++++++++++++++-------- 1 file changed, 31 insertions(+), 8 deletions(-) diff --git a/compiler/simplCore/SetLevels.hs b/compiler/simplCore/SetLevels.hs index afca7ae..2b533b7 100644 --- a/compiler/simplCore/SetLevels.hs +++ b/compiler/simplCore/SetLevels.hs @@ -81,7 +81,7 @@ import Var import VarSet import VarEnv import Literal ( litIsTrivial ) -import Demand ( StrictSig, isStrictDmd, splitStrictSig, increaseStrictSigArity ) +import Demand ( StrictSig, Demand, isStrictDmd, splitStrictSig, increaseStrictSigArity ) import Name ( getOccName, mkSystemVarName ) import OccName ( occNameString ) import Type ( Type, mkLamTypes, splitTyConApp_maybe ) @@ -95,7 +95,7 @@ import FastString import UniqDFM import FV import Data.Maybe -import Control.Monad ( zipWithM ) +import MonadUtils ( mapAccumLM ) {- ************************************************************************ @@ -402,7 +402,7 @@ lvlApp env orig_expr ((_,AnnVar fn), args) ; return (foldl App lapp' rargs') } | otherwise - = do { args' <- zipWithM (lvlMFE env) stricts args + = do { (_, args') <- mapAccumLM lvl_arg stricts args -- Take account of argument strictness; see -- Note [Floating to the top] ; return (foldl App (lookupVar env fn) args') } @@ -410,12 +410,12 @@ lvlApp env orig_expr ((_,AnnVar fn), args) n_val_args = count (isValArg . deAnnotate) args arity = idArity fn - stricts :: [Bool] -- True for strict argument + stricts :: [Demand] -- True for strict /value/ arguments stricts = case splitStrictSig (idStrictness fn) of - (arg_ds, _) | not (arg_ds `lengthExceeds` n_val_args) - -> map isStrictDmd arg_ds ++ repeat False + (arg_ds, _) | arg_ds `lengthExceeds` n_val_args + -> [] | otherwise - -> repeat False + -> arg_ds -- Separate out the PAP that we are floating from the extra -- arguments, by traversing the spine until we have collected @@ -428,6 +428,19 @@ lvlApp env orig_expr ((_,AnnVar fn), args) | otherwise = left n f (a:rargs) left _ _ _ = panic "SetLevels.lvlExpr.left" + is_val_arg :: CoreExprWithFVs -> Bool + is_val_arg (_, AnnType {}) = False + is_val_arg _ = True + + lvl_arg :: [Demand] -> CoreExprWithFVs -> LvlM ([Demand], LevelledExpr) + lvl_arg strs arg | (str1 : strs') <- strs + , is_val_arg arg + = do { arg' <- lvlMFE env (isStrictDmd str1) arg + ; return (strs', arg') } + | otherwise + = do { arg' <- lvlMFE env False arg + ; return (strs, arg') } + lvlApp env _ (fun, args) = -- No PAPs that we can float: just carry on with the -- arguments and the function. @@ -893,7 +906,17 @@ in exchange we build a thunk, which is bad. This case reduces allocation by 7% in spectral/puzzle (a rather strange benchmark) and 1.2% in real/fem. Doesn't change any other allocation at all. -We will make a separate decision for the scrutinees and alternatives. +We will make a separate decision for the scrutinee and alternatives. + +However this can have a knock-on effect for fusion: consider + \v -> foldr k z (case x of I# y -> build ..y..) +Perhaps we can float the entire (case x of ...) out of the \v. Then +fusion will not happen, but we will get more sharing. But if we don't +float the case (as advocated here) we won't float the (build ...y..) +either, so fusion will happen. It can be a big effect, esp in some +artificial benchmarks (e.g. integer, queens), but there is no perfect +answer. + -} annotateBotStr :: Id -> Arity -> Maybe (Arity, StrictSig) -> Id From git at git.haskell.org Tue May 2 09:14:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 May 2017 09:14:34 +0000 (UTC) Subject: [commit: ghc] master: Join-point refactoring (71037b6) Message-ID: <20170502091434.4B77F3A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/71037b61597d8e80ba5acebc8ad2295e5266dc07/ghc >--------------------------------------------------------------- commit 71037b61597d8e80ba5acebc8ad2295e5266dc07 Author: Simon Peyton Jones Date: Thu Apr 27 17:04:14 2017 +0100 Join-point refactoring This commit has a raft of refactorings that improve the treatment of join points. I wasn't aiming so much as to gain performance as to make the code simpler. The two big things are these: * Make mkDupableCont work for SimplBind as well. This is simpler than I thought and quite neat. (Luke had aready done StrictArg.) That's a win in its own right. But also now /all/ continuations can be made dup-able * Now that all continuations can be made dup-able, I could simplify mkDupableCont to return just one SimplCont, instead of two. That really is a worthwhile simlification! Much easier to think about. Plus a bunch of smaller things: * Remove the join-arity that had been added to seIdSubst. It can be done more simply by putting it in DoneEx, which is the only constructor that actually needs it, and now we don't need the unsavoury isJoinIdInEnv_maybe. * Re-order the handling of join points in Simplify, so that we don't need the horrible resultTypeOfDupableCont * Add field names for StrictBind, StrictArg; and use them * Define simplMonad.newJoinId, and use it * Rename the seFloats field of SimplEnv to seLetFloats Binary sizes seem to go up slightly, but allocations generally improve, sometimes significantly. I don't believe the runtime numbers are reliable enough to draw any conclusions about -------------------------------------------------------------------------------- Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- event +1.1% -12.0% -0.2% -0.2% -8.7% fulsom +1.9% -11.8% -10.0% -10.0% +5.3% last-piece +2.3% -1.2% -1.2% -1.2% +0.0% mate +0.9% -1.4% -0.6% -0.7% +0.0% multiplier +1.5% -8.3% 0.17 0.17 +0.0% parser +2.0% +1.0% 0.04 0.04 +0.0% parstof +1.5% +0.7% 0.01 0.01 +0.0% sched +1.3% -6.1% 0.03 0.03 +0.0% simple +1.8% +1.0% +9.7% +9.6% +0.0% -------------------------------------------------------------------------------- Min +0.5% -12.0% -10.0% -10.0% -8.7% Max +3.0% +1.0% +14.2% +14.2% +50.0% Geometric Mean +1.4% -0.4% +0.3% +0.4% +0.5% There's also a tests/perf/compiler improvement of 20% allocation in T6048. I think it's because we now generate smaller code. >--------------------------------------------------------------- 71037b61597d8e80ba5acebc8ad2295e5266dc07 compiler/simplCore/SimplEnv.hs | 237 ++++---- compiler/simplCore/SimplMonad.hs | 20 +- compiler/simplCore/SimplUtils.hs | 125 ++-- compiler/simplCore/Simplify.hs | 627 +++++++++++---------- testsuite/tests/perf/compiler/all.T | 3 +- .../tests/simplCore/should_compile/T12603.stdout | 2 +- .../tests/simplCore/should_compile/T3234.stderr | 10 +- 7 files changed, 548 insertions(+), 476 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 71037b61597d8e80ba5acebc8ad2295e5266dc07 From git at git.haskell.org Tue May 2 11:10:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 May 2017 11:10:16 +0000 (UTC) Subject: [commit: ghc] master: Fix loss-of-SpecConstr bug (9e47dc4) Message-ID: <20170502111016.38CF03A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9e47dc451788cce20acb6a8208c56a7e4dbe246b/ghc >--------------------------------------------------------------- commit 9e47dc451788cce20acb6a8208c56a7e4dbe246b Author: Simon Peyton Jones Date: Tue May 2 12:04:44 2017 +0100 Fix loss-of-SpecConstr bug This bug, reported in Trac #13623 has been present since commit b8b3e30a6eedf9f213b8a718573c4827cfa230ba Author: Edward Z. Yang Date: Fri Jun 24 11:03:47 2016 -0700 Axe RecFlag on TyCons. SpecConstr tries not to specialise indefinitely, and had a limit (see Note [Limit recursive specialisation]) that made use of info about whether or not a data constructor was "recursive". This info vanished in the above commit, making the limit fire much more often -- and indeed it fired in this test case, in a situation where specialisation is /highly/ desirable. I refactored the test, to look instead at the number of iterations of the loop of "and now specialise calls that arise from the specialisation". Actually less code, and more robust. I also added record field names to a couple of constructors, and renamed RuleInfo to SpecInfo. >--------------------------------------------------------------- 9e47dc451788cce20acb6a8208c56a7e4dbe246b compiler/specialise/SpecConstr.hs | 193 ++++++++++++++------------ testsuite/tests/perf/should_run/T13623.hs | 82 +++++++++++ testsuite/tests/perf/should_run/T13623.stdout | 1 + testsuite/tests/perf/should_run/all.T | 8 ++ 4 files changed, 198 insertions(+), 86 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 9e47dc451788cce20acb6a8208c56a7e4dbe246b From git at git.haskell.org Tue May 2 11:26:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 May 2017 11:26:14 +0000 (UTC) Subject: [commit: ghc] master: Typos in manual and comments (b1aede6) Message-ID: <20170502112614.E4BAE3A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b1aede61350a9c0a33c6d034de93a249c000a84c/ghc >--------------------------------------------------------------- commit b1aede61350a9c0a33c6d034de93a249c000a84c Author: Gabor Greif Date: Tue May 2 13:25:33 2017 +0200 Typos in manual and comments >--------------------------------------------------------------- b1aede61350a9c0a33c6d034de93a249c000a84c compiler/coreSyn/CoreSubst.hs | 2 +- compiler/rename/RnEnv.hs | 2 +- compiler/simplStg/StgCse.hs | 2 +- docs/users_guide/glasgow_exts.rst | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/compiler/coreSyn/CoreSubst.hs b/compiler/coreSyn/CoreSubst.hs index 640c7f1..919d9e8 100644 --- a/compiler/coreSyn/CoreSubst.hs +++ b/compiler/coreSyn/CoreSubst.hs @@ -723,7 +723,7 @@ The functions that substitute over IdInfo must be pretty lazy, because they are knot-tied by substRecBndrs. One case in point was Trac #10627 in which a rule for a function 'f' -referred to 'f' (at a differnet type) on the RHS. But instead of just +referred to 'f' (at a different type) on the RHS. But instead of just substituting in the rhs of the rule, we were calling simpleOptExpr, which looked at the idInfo for 'f'; result <>. diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs index 3aa9472..570c6c0 100644 --- a/compiler/rename/RnEnv.hs +++ b/compiler/rename/RnEnv.hs @@ -609,7 +609,7 @@ TH we might use the same TH NameU in two different name spaces. eg (Trac #7241): $(newName "Foo" >>= \o -> return [DataD [] o [] [RecC o []] [''Show]]) Here we generate a type constructor and data constructor with the same -unique, but differnt name spaces. +unique, but different name spaces. It'd be nicer to rule this out in extendGlobalRdrEnvRn, but that would mean looking up the OccName in every name-space, just in case, and that diff --git a/compiler/simplStg/StgCse.hs b/compiler/simplStg/StgCse.hs index ec4b188..6bd6adc 100644 --- a/compiler/simplStg/StgCse.hs +++ b/compiler/simplStg/StgCse.hs @@ -26,7 +26,7 @@ which produces this Core: bar :: forall a. a -> (Either Int a, Either Bool a) bar @a x = (Right @Int @a x, Right @Bool @a x) -where the two components of the tuple are differnt terms, and cannot be +where the two components of the tuple are different terms, and cannot be commoned up (easily). On the STG level we have bar [x] = let c1 = Right [x] diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 0a09c7c..6e394e7 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -7196,7 +7196,7 @@ precisely the same as type given in the instance head. For example: :: instance Eq (Elem [e]) => Collects [e] where -- Choose one of the following alternatives: type Elem [e] = e -- OK - type Elem [x] = x -- BAD; '[x]' is differnet to '[e]' from head + type Elem [x] = x -- BAD; '[x]' is different to '[e]' from head type Elem x = x -- BAD; 'x' is different to '[e]' type Elem [Maybe x] = x -- BAD: '[Maybe x]' is different to '[e]' From git at git.haskell.org Tue May 2 13:41:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 May 2017 13:41:09 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Improve SpecConstr when there are many opportunities (324eeb9) Message-ID: <20170502134109.D00F73A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/324eeb9448a4e854003dd9b5709e1939da25cb12/ghc >--------------------------------------------------------------- commit 324eeb9448a4e854003dd9b5709e1939da25cb12 Author: Simon Peyton Jones Date: Thu Apr 27 11:15:00 2017 +0100 Improve SpecConstr when there are many opportunities SpecConstr has -fspec-contr-count=N which limits the maximum number of specialisations we make for any particular function. But until now, if that limit was exceeded we discarded all the candidates! So adding a new specialisaiton opportunity (by adding a new call site, or improving the optimiser) could result in less specialisation and worse performance. This patch instead picks the top N candidates, resulting in less brittle behaviour. See Note [Choosing patterns]. (cherry picked from commit c46a600f320b25e0ac73107acdb12a33d7fbd9c3) >--------------------------------------------------------------- 324eeb9448a4e854003dd9b5709e1939da25cb12 compiler/specialise/SpecConstr.hs | 156 +++++++++++++++++++++++++++----------- 1 file changed, 113 insertions(+), 43 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 324eeb9448a4e854003dd9b5709e1939da25cb12 From git at git.haskell.org Tue May 2 13:41:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 May 2017 13:41:13 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix loss-of-SpecConstr bug (7850538) Message-ID: <20170502134113.13BD13A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/78505384d5e4c44e525dda7aa5a9ca7ff9e3ca22/ghc >--------------------------------------------------------------- commit 78505384d5e4c44e525dda7aa5a9ca7ff9e3ca22 Author: Simon Peyton Jones Date: Tue May 2 12:04:44 2017 +0100 Fix loss-of-SpecConstr bug This bug, reported in Trac #13623 has been present since commit b8b3e30a6eedf9f213b8a718573c4827cfa230ba Author: Edward Z. Yang Date: Fri Jun 24 11:03:47 2016 -0700 Axe RecFlag on TyCons. SpecConstr tries not to specialise indefinitely, and had a limit (see Note [Limit recursive specialisation]) that made use of info about whether or not a data constructor was "recursive". This info vanished in the above commit, making the limit fire much more often -- and indeed it fired in this test case, in a situation where specialisation is /highly/ desirable. I refactored the test, to look instead at the number of iterations of the loop of "and now specialise calls that arise from the specialisation". Actually less code, and more robust. I also added record field names to a couple of constructors, and renamed RuleInfo to SpecInfo. (cherry picked from commit 9e47dc451788cce20acb6a8208c56a7e4dbe246b) >--------------------------------------------------------------- 78505384d5e4c44e525dda7aa5a9ca7ff9e3ca22 compiler/specialise/SpecConstr.hs | 193 ++++++++++++++------------ testsuite/tests/perf/should_run/T13623.hs | 82 +++++++++++ testsuite/tests/perf/should_run/T13623.stdout | 1 + testsuite/tests/perf/should_run/all.T | 8 ++ 4 files changed, 198 insertions(+), 86 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 78505384d5e4c44e525dda7aa5a9ca7ff9e3ca22 From git at git.haskell.org Tue May 2 21:14:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 May 2017 21:14:54 +0000 (UTC) Subject: [commit: ghc] branch 'wip/dfeuer-interleave-mvars' created Message-ID: <20170502211454.9DEF53A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/dfeuer-interleave-mvars Referencing: fdd659bf85617983c2a3da16a5ceb28a16f65cf9 From git at git.haskell.org Tue May 2 21:14:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 May 2017 21:14:57 +0000 (UTC) Subject: [commit: ghc] wip/dfeuer-interleave-mvars: Speed up fixIO (8b552dd) Message-ID: <20170502211457.656EA3A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/dfeuer-interleave-mvars Link : http://ghc.haskell.org/trac/ghc/changeset/8b552dd317d9e93d715eee9aac3723c9b82d5166/ghc >--------------------------------------------------------------- commit 8b552dd317d9e93d715eee9aac3723c9b82d5166 Author: David Feuer Date: Tue May 2 12:15:04 2017 -0400 Speed up fixIO `unsafeInterleaveIO` now includes an expensive `noDuplicate`. Since this code was written to work in the presence of duplication, that shouldn't be necessary. Switched from `takeMVar` to `readMVar` per Simon M, as we now have an atomic `readMVar#`. >--------------------------------------------------------------- 8b552dd317d9e93d715eee9aac3723c9b82d5166 libraries/base/System/IO.hs | 20 +++++++++++++------- 1 file changed, 13 insertions(+), 7 deletions(-) diff --git a/libraries/base/System/IO.hs b/libraries/base/System/IO.hs index 735d41b..fde5bb6 100644 --- a/libraries/base/System/IO.hs +++ b/libraries/base/System/IO.hs @@ -403,7 +403,7 @@ withBinaryFile name mode = bracket (openBinaryFile name mode) hClose fixIO :: (a -> IO a) -> IO a fixIO k = do m <- newEmptyMVar - ans <- unsafeInterleaveIO (takeMVar m) + ans <- unsafeDupableInterleaveIO (readMVar m) result <- k ans putMVar m result return result @@ -413,12 +413,18 @@ fixIO k = do -- computation a few times before it notices the loop, which is wrong. -- -- NOTE2: the explicit black-holing with an IORef ran into trouble --- with multiple threads (see #5421), so now we use an MVar. I'm --- actually wondering whether we should use readMVar rather than --- takeMVar, just in case it ends up being executed multiple times, --- but even then it would have to be masked to protect against async --- exceptions. Ugh. What we really need here is an IVar, or an --- atomic readMVar, or even STM. All these seem like overkill. +-- with multiple threads (see #5421), so now we use an MVar. We used +-- to use takeMVar with unsafeInterleaveIO. This, however, uses noDuplicate#, +-- which is not particularly cheap. Better to use readMVar, which can be +-- performed in multiple threads safely, and to use unsafeDupableInterleaveIO +-- to avoid the noDuplicate cost. +-- +-- What we'd ideally want is probably an IVar, but we don't quite have those. +-- STM TVars look like an option at first, but I don't think they are: +-- we'd need to be able to write to the variable in an IO context, which can +-- only be done using 'atomically', and 'atomically' is not allowed within +-- unsafePerformIO. We can't know if someone will try to use the result +-- of fixIO with unsafePerformIO! -- -- See also System.IO.Unsafe.unsafeFixIO. -- From git at git.haskell.org Tue May 2 21:15:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 May 2017 21:15:00 +0000 (UTC) Subject: [commit: ghc] wip/dfeuer-interleave-mvars: Implement unsafeInterleaveIO using MVars (fdd659b) Message-ID: <20170502211500.20CE43A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/dfeuer-interleave-mvars Link : http://ghc.haskell.org/trac/ghc/changeset/fdd659bf85617983c2a3da16a5ceb28a16f65cf9/ghc >--------------------------------------------------------------- commit fdd659bf85617983c2a3da16a5ceb28a16f65cf9 Author: David Feuer Date: Tue May 2 17:09:00 2017 -0400 Implement unsafeInterleaveIO using MVars Summary: Previously, `unsafeInterleaveIO` used `noDuplicate` to prevent the computation from being run twice. `noDuplicate` needs to walk the evaluation stack. This experimental implementation instead uses `MVar`s to prevent duplication. Reviewers: austin, hvr, bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3526 >--------------------------------------------------------------- fdd659bf85617983c2a3da16a5ceb28a16f65cf9 libraries/base/GHC/IO/Unsafe.hs | 19 ++++++++++++++++--- 1 file changed, 16 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/IO/Unsafe.hs b/libraries/base/GHC/IO/Unsafe.hs index c1c07ae..5498e19 100644 --- a/libraries/base/GHC/IO/Unsafe.hs +++ b/libraries/base/GHC/IO/Unsafe.hs @@ -26,7 +26,7 @@ module GHC.IO.Unsafe ( ) where import GHC.Base - +import GHC.MVar {-| This is the \"back door\" into the 'IO' monad, allowing @@ -111,12 +111,25 @@ file reading, see 'System.IO.hGetContents'. -} {-# INLINE unsafeInterleaveIO #-} unsafeInterleaveIO :: IO a -> IO a -unsafeInterleaveIO m = unsafeDupableInterleaveIO (noDuplicate >> m) +unsafeInterleaveIO m = do + claimedV <- newEmptyMVar + resultV <- newEmptyMVar + unsafeDupableInterleaveIO $ do + claimSucceeded <- tryPutMVar claimedV () + if claimSucceeded + then do + -- We were the first ones to claim the computation, so we + -- perform it and store the result. + res <- m + putMVar resultV res + pure res + else readMVar resultV + -- Note [unsafeDupableInterleaveIO should not be inlined] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -- --- We used to believe that INLINE on unsafeInterleaveIO was safe, +-- We used to believe that INLINE on unsafeDupableInterleaveIO was safe, -- because the state from this IO thread is passed explicitly to the -- interleaved IO, so it cannot be floated out and shared. -- From git at git.haskell.org Wed May 3 03:07:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 May 2017 03:07:53 +0000 (UTC) Subject: [commit: ghc] master: Fix #13233 by checking for lev-poly primops (b460d6c) Message-ID: <20170503030753.BE29C3A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b460d6c99316deac2b8022a4fb7dddc57c052a2a/ghc >--------------------------------------------------------------- commit b460d6c99316deac2b8022a4fb7dddc57c052a2a Author: Richard Eisenberg Date: Tue May 2 18:56:30 2017 -0400 Fix #13233 by checking for lev-poly primops The implementation plan is all in Note [Detecting forced eta expansion] in DsExpr. Test Plan: ./validate, codeGen/should_fail/T13233 Reviewers: simonpj, austin, bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13233 Differential Revision: https://phabricator.haskell.org/D3490 >--------------------------------------------------------------- b460d6c99316deac2b8022a4fb7dddc57c052a2a compiler/coreSyn/CoreLint.hs | 4 +- compiler/coreSyn/CoreSyn.hs | 3 +- compiler/deSugar/Check.hs | 2 +- compiler/deSugar/DsArrows.hs | 4 +- compiler/deSugar/DsExpr.hs | 262 +++++++++++++++------- compiler/deSugar/DsMonad.hs | 3 +- compiler/hsSyn/HsExpr.hs | 3 + compiler/hsSyn/HsUtils.hs | 7 +- compiler/typecheck/TcBinds.hs | 2 +- compiler/typecheck/TcExpr.hs | 20 +- compiler/typecheck/TcMatches.hs | 4 +- compiler/typecheck/TcSplice.hs | 4 +- compiler/types/Kind.hs | 40 ---- testsuite/tests/codeGen/should_compile/T13233.hs | 12 - testsuite/tests/codeGen/should_compile/all.T | 1 - testsuite/tests/codeGen/should_fail/T13233.hs | 27 +++ testsuite/tests/codeGen/should_fail/T13233.stderr | 24 ++ testsuite/tests/codeGen/should_fail/all.T | 1 + 18 files changed, 269 insertions(+), 154 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 b460d6c99316deac2b8022a4fb7dddc57c052a2a From git at git.haskell.org Wed May 3 03:07:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 May 2017 03:07:56 +0000 (UTC) Subject: [commit: ghc] master: Shave the hair off mkCastTy. (ef0ff34) Message-ID: <20170503030756.8FB993A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ef0ff34d462e3780210567a13d58b868ec3399e0/ghc >--------------------------------------------------------------- commit ef0ff34d462e3780210567a13d58b868ec3399e0 Author: Richard Eisenberg Date: Fri Apr 7 11:38:37 2017 -0400 Shave the hair off mkCastTy. Previously, mkCastTy went to great lengths to shove casts around. But this doesn't seem to be necessary. However, the reflexivity check currently in mkCastTy is not enough. See the abortive Note [No reflexive casts in types] >--------------------------------------------------------------- ef0ff34d462e3780210567a13d58b868ec3399e0 compiler/types/Type.hs | 135 +++++++-------------- .../tests/typecheck/should_fail/T10619.stderr | 4 +- 2 files changed, 46 insertions(+), 93 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 ef0ff34d462e3780210567a13d58b868ec3399e0 From git at git.haskell.org Wed May 3 03:07:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 May 2017 03:07:59 +0000 (UTC) Subject: [commit: ghc] master: Fix #13333 by fixing the covar's type in ctEvCoercion (09bf135) Message-ID: <20170503030759.E8BA03A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/09bf135ace55ce2572bf4168124d631e386c64bb/ghc >--------------------------------------------------------------- commit 09bf135ace55ce2572bf4168124d631e386c64bb Author: Richard Eisenberg Date: Sun Apr 23 10:24:30 2017 -0400 Fix #13333 by fixing the covar's type in ctEvCoercion The change is noted in Note [Given in ctEvCoercion]. This patch also adds a bit more commentary to TcFlatten, documenting some key invariants of the flattening algorithm. While in the area, I also removed some stale commentary from TcCanonical. >--------------------------------------------------------------- 09bf135ace55ce2572bf4168124d631e386c64bb compiler/typecheck/TcCanonical.hs | 98 ++++------------------ compiler/typecheck/TcFlatten.hs | 88 +++++++++++++++++-- compiler/typecheck/TcRnTypes.hs | 21 +++-- compiler/typecheck/TcSMonad.hs | 1 + testsuite/tests/typecheck/should_compile/T13333.hs | 28 +++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 6 files changed, 143 insertions(+), 94 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 09bf135ace55ce2572bf4168124d631e386c64bb From git at git.haskell.org Wed May 3 03:08:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 May 2017 03:08:02 +0000 (UTC) Subject: [commit: ghc] master: Use mkCastTy in subst_ty. (466803a) Message-ID: <20170503030802.B60E13A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/466803a0e9628ccd5feb55d062e141e0972fc19c/ghc >--------------------------------------------------------------- commit 466803a0e9628ccd5feb55d062e141e0972fc19c Author: Richard Eisenberg Date: Fri Apr 7 11:39:51 2017 -0400 Use mkCastTy in subst_ty. This allows mkCastTy to maintain invariants. Much like how we use mkAppTy in subst_ty. >--------------------------------------------------------------- 466803a0e9628ccd5feb55d062e141e0972fc19c compiler/types/TyCoRep.hs | 4 ++-- compiler/types/Type.hs | 11 ----------- compiler/types/Type.hs-boot | 3 ++- 3 files changed, 4 insertions(+), 14 deletions(-) diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index 52a0f1d..300ef80 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -135,7 +135,7 @@ module TyCoRep ( import {-# SOURCE #-} DataCon( dataConFullSig , dataConUnivTyVarBinders, dataConExTyVarBinders , DataCon, filterEqSpec ) -import {-# SOURCE #-} Type( isPredTy, isCoercionTy, mkAppTy +import {-# SOURCE #-} Type( isPredTy, isCoercionTy, mkAppTy, mkCastTy , tyCoVarsOfTypesWellScoped , tyCoVarsOfTypeWellScoped , coreView, typeKind ) @@ -2186,7 +2186,7 @@ subst_ty subst ty (ForAllTy $! ((TvBndr $! tv') vis)) $! (subst_ty subst' ty) go (LitTy n) = LitTy $! n - go (CastTy ty co) = (CastTy $! (go ty)) $! (subst_co subst co) + go (CastTy ty co) = (mkCastTy $! (go ty)) $! (subst_co subst co) go (CoercionTy co) = CoercionTy $! (subst_co subst co) substTyVar :: TCvSubst -> TyVar -> Type diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index e0a98e9..7750a35 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -1222,10 +1222,6 @@ mkCastTy ty co | isReflexiveCo co = ty mkCastTy (CastTy ty co1) co2 = mkCastTy ty (co1 `mkTransCo` co2) mkCastTy ty co = CastTy ty co -tyConTyBinders :: TyCon -> [TyBinder] --- Return the tyConBinders in TyBinder form -tyConTyBinders tycon = tyConBindersTyBinders (tyConBinders tycon) - tyConBindersTyBinders :: [TyConBinder] -> [TyBinder] -- Return the tyConBinders in TyBinder form tyConBindersTyBinders = map to_tyb @@ -1529,13 +1525,6 @@ caseBinder :: TyBinder -- ^ binder to scrutinize caseBinder (Named v) f _ = f v caseBinder (Anon t) _ d = d t --- | Create a TCvSubst combining the binders and types provided. --- NB: It is specifically OK if the lists are of different lengths. --- Barely used -zipTyBinderSubst :: [TyBinder] -> [Type] -> TCvSubst -zipTyBinderSubst bndrs tys - = mkTvSubstPrs [ (tv, ty) | (Named (TvBndr tv _), ty) <- zip bndrs tys ] - -- | Manufacture a new 'TyConBinder' from a 'TyBinder'. Anonymous -- 'TyBinder's are still assigned names as 'TyConBinder's, so we need -- the extra gunk with which to construct a 'Name'. Used when producing diff --git a/compiler/types/Type.hs-boot b/compiler/types/Type.hs-boot index be7e4ed..2fc251a 100644 --- a/compiler/types/Type.hs-boot +++ b/compiler/types/Type.hs-boot @@ -3,13 +3,14 @@ module Type where import TyCon import Var ( TyVar ) -import {-# SOURCE #-} TyCoRep( Type, Kind ) +import {-# SOURCE #-} TyCoRep( Type, Coercion, Kind ) import Util isPredTy :: Type -> Bool isCoercionTy :: Type -> Bool mkAppTy :: Type -> Type -> Type +mkCastTy :: Type -> Coercion -> Type piResultTy :: Type -> Type -> Type typeKind :: Type -> Kind From git at git.haskell.org Wed May 3 03:08:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 May 2017 03:08:05 +0000 (UTC) Subject: [commit: ghc] master: Fix #13233 by checking for lev-poly primops (16b0a07) Message-ID: <20170503030805.718D43A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/16b0a07e5d0c72c1171359e546d9373442ec0564/ghc >--------------------------------------------------------------- commit 16b0a07e5d0c72c1171359e546d9373442ec0564 Author: Richard Eisenberg Date: Sun Apr 23 14:16:32 2017 -0400 Fix #13233 by checking for lev-poly primops The implementation plan is all in Note [Detecting forced eta expansion] in DsExpr. >--------------------------------------------------------------- 16b0a07e5d0c72c1171359e546d9373442ec0564 testsuite/tests/codeGen/should_fail/T13233.stderr | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/codeGen/should_fail/T13233.stderr b/testsuite/tests/codeGen/should_fail/T13233.stderr index 2d167cf..c1cbb97 100644 --- a/testsuite/tests/codeGen/should_fail/T13233.stderr +++ b/testsuite/tests/codeGen/should_fail/T13233.stderr @@ -2,7 +2,7 @@ T13233.hs:14:11: error: Cannot use primitive with levity-polymorphic arguments: GHC.Prim.(#,#) :: a -> a -> (# a, a #) - Levity polymorphic arguments: + Levity-polymorphic arguments: a :: TYPE rep a :: TYPE rep @@ -10,7 +10,7 @@ T13233.hs:22:16: error: Cannot use primitive with levity-polymorphic arguments: GHC.Prim.(#,#) :: forall (a :: TYPE rep1) (b :: TYPE rep2). a -> b -> (# a, b #) - Levity polymorphic arguments: + Levity-polymorphic arguments: a :: TYPE rep1 b :: TYPE rep2 @@ -21,4 +21,4 @@ T13233.hs:27:10: error: -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #) - Levity polymorphic arguments: a :: TYPE rep + Levity-polymorphic arguments: a :: TYPE rep From git at git.haskell.org Wed May 3 03:08:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 May 2017 03:08:08 +0000 (UTC) Subject: [commit: ghc] master: Test #13585 in typecheck/should_compile/T13585 (6df8bef) Message-ID: <20170503030808.F0CE23A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6df8bef054db0b95bb8f9e55bb82580e27d251d6/ghc >--------------------------------------------------------------- commit 6df8bef054db0b95bb8f9e55bb82580e27d251d6 Author: Richard Eisenberg Date: Mon May 1 23:16:20 2017 -0400 Test #13585 in typecheck/should_compile/T13585 >--------------------------------------------------------------- 6df8bef054db0b95bb8f9e55bb82580e27d251d6 testsuite/tests/typecheck/should_compile/Makefile | 6 ++ testsuite/tests/typecheck/should_compile/T13585.hs | 5 ++ .../tests/typecheck/should_compile/T13585a.hs | 81 ++++++++++++++++++++++ .../tests/typecheck/should_compile/T13585b.hs | 7 ++ testsuite/tests/typecheck/should_compile/all.T | 1 + 5 files changed, 100 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/Makefile b/testsuite/tests/typecheck/should_compile/Makefile index cb8269a..fc90899 100644 --- a/testsuite/tests/typecheck/should_compile/Makefile +++ b/testsuite/tests/typecheck/should_compile/Makefile @@ -56,3 +56,9 @@ Tc271: '$(TEST_HC)' $(TEST_HC_OPTS) -c Tc271.hs-boot '$(TEST_HC)' $(TEST_HC_OPTS) -c Tc271a.hs '$(TEST_HC)' $(TEST_HC_OPTS) -c Tc271.hs + +T13585: + $(RM) -f T13585a.o T13585a.hi T13585b.o T13585b.hi T13585.o T13585.hi + '$(TEST_HC)' $(TEST_HC_OPTS) -c T13585a.hs -O + '$(TEST_HC)' $(TEST_HC_OPTS) -c T13585b.hs -O + '$(TEST_HC)' $(TEST_HC_OPTS) -c T13585.hs -O diff --git a/testsuite/tests/typecheck/should_compile/T13585.hs b/testsuite/tests/typecheck/should_compile/T13585.hs new file mode 100644 index 0000000..74c9412 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13585.hs @@ -0,0 +1,5 @@ +module T13585 where +import T13585b (extractZonedTime) + +main :: IO () +main = print extractZonedTime diff --git a/testsuite/tests/typecheck/should_compile/T13585a.hs b/testsuite/tests/typecheck/should_compile/T13585a.hs new file mode 100644 index 0000000..fda3d70 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13585a.hs @@ -0,0 +1,81 @@ +{-# LANGUAGE KindSignatures, RankNTypes, TypeFamilies, MultiParamTypeClasses, FlexibleInstances,UndecidableInstances #-} + +module T13585a where + +import Data.Monoid (First(..)) +import Data.Functor.Identity + +class Profunctor p where + dimap :: (a -> b) -> (c -> d) -> p b c -> p a d + dimap f g = lmap f . rmap g + {-# INLINE dimap #-} + + lmap :: (a -> b) -> p b c -> p a c + lmap f = dimap f id + {-# INLINE lmap #-} + + rmap :: (b -> c) -> p a b -> p a c + rmap = dimap id + {-# INLINE rmap #-} + + +data Exchange a b s t = Exchange (s -> a) (b -> t) + +instance Functor (Exchange a b s) where + fmap f (Exchange sa bt) = Exchange sa (f . bt) + {-# INLINE fmap #-} + +instance Profunctor (Exchange a b) where + dimap f g (Exchange sa bt) = Exchange (sa . f) (g . bt) + {-# INLINE dimap #-} + lmap f (Exchange sa bt) = Exchange (sa . f) bt + {-# INLINE lmap #-} + rmap f (Exchange sa bt) = Exchange sa (f . bt) + {-# INLINE rmap #-} + + + +withIso :: AnIso s t a b -> ((s -> a) -> (b -> t) -> r) -> r +withIso ai k = case ai (Exchange id Identity) of + Exchange sa bt -> k sa (runIdentity undefined bt) +{-# INLINE withIso #-} + +type Iso s t a b = forall p f. (Profunctor p, Functor f) => p a (f b) -> p s (f t) +type Iso' s a = Iso s s a a +type AnIso s t a b = Exchange a b a (Identity b) -> Exchange a b s (Identity t) + +class (Rewrapped s t, Rewrapped t s) => Rewrapping s t +instance (Rewrapped s t, Rewrapped t s) => Rewrapping s t + + +instance (t ~ First b) => Rewrapped (First a) t +instance Wrapped (First a) where + type Unwrapped (First a) = Maybe a + _Wrapped' = iso getFirst First + {-# INLINE _Wrapped' #-} + +class Wrapped s => Rewrapped (s :: *) (t :: *) + +class Wrapped s where + type Unwrapped s :: * + _Wrapped' :: Iso' s (Unwrapped s) + +_Wrapping :: Rewrapping s t => (Unwrapped s -> s) -> Iso s t (Unwrapped s) (Unwrapped t) +_Wrapping _ = _Wrapped +{-# INLINE _Wrapping #-} + +iso :: (s -> a) -> (b -> t) -> Iso s t a b +iso sa bt = dimap sa (fmap bt) +{-# INLINE iso #-} + +_Wrapped :: Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t) +_Wrapped = withIso _Wrapped' $ \ sa _ -> withIso _Wrapped' $ \ _ bt -> iso sa bt +{-# INLINE _Wrapped #-} + +au :: Functor f => AnIso s t a b -> ((b -> t) -> f s) -> f a +au k = withIso k $ \ sa bt f -> fmap sa (f bt) +{-# INLINE au #-} + +ala :: (Functor f, Rewrapping s t) => (Unwrapped s -> s) -> ((Unwrapped t -> t) -> f s) -> f (Unwrapped s) +ala = au . _Wrapping +{-# INLINE ala #-} diff --git a/testsuite/tests/typecheck/should_compile/T13585b.hs b/testsuite/tests/typecheck/should_compile/T13585b.hs new file mode 100644 index 0000000..db09cf1 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13585b.hs @@ -0,0 +1,7 @@ +module T13585b where + +import T13585a +import Data.Monoid + +extractZonedTime :: Maybe () +extractZonedTime = ala First foldMap [Nothing] diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 8742353..34b8184 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -557,3 +557,4 @@ test('T13509', normal, compile, ['']) test('T13526', normal, compile, ['']) test('T13603', normal, compile, ['']) test('T13333', normal, compile, ['']) +test('T13585', [extra_files(['T13585.hs', 'T13585a.hs', 'T13585b.hs'])], run_command, ['$MAKE -s --no-print-directory T13585']) From git at git.haskell.org Wed May 3 13:27:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 May 2017 13:27:02 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Comments only (0cdb357) Message-ID: <20170503132702.A4C3A3A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/0cdb3579c1f48308e37d6ae5524f1993239f201f/ghc >--------------------------------------------------------------- commit 0cdb3579c1f48308e37d6ae5524f1993239f201f Author: Simon Peyton Jones Date: Tue Apr 25 13:15:44 2017 +0100 Comments only (cherry picked from commit 4d5ab1f89ab4c082c10f67616ca4308d67923486) >--------------------------------------------------------------- 0cdb3579c1f48308e37d6ae5524f1993239f201f compiler/typecheck/TcRnTypes.hs | 22 +++++++++++++++------- 1 file changed, 15 insertions(+), 7 deletions(-) diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index 1364027..e52772d 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -85,7 +85,7 @@ module TcRnTypes( andWC, unionsWC, mkSimpleWC, mkImplicWC, addInsols, getInsolubles, insolublesOnly, addSimples, addImplics, tyCoVarsOfWC, dropDerivedWC, dropDerivedSimples, dropDerivedInsols, - tyCoVarsOfWCList, + tyCoVarsOfWCList, trulyInsoluble, isDroppableDerivedLoc, insolubleImplic, arisesFromGivens, @@ -2374,7 +2374,11 @@ So a Given has EvVar inside it rather than (as previously) an EvTerm. -- EvVarDest. data TcEvDest = EvVarDest EvVar -- ^ bind this var to the evidence + -- EvVarDest is always used for non-type-equalities + -- e.g. class constraints + | HoleDest CoercionHole -- ^ fill in this hole with the evidence + -- HoleDest is always used for type-equalities -- See Note [Coercion holes] in TyCoRep data CtEvidence @@ -2421,12 +2425,16 @@ ctEvTerm ev@(CtWanted { ctev_dest = HoleDest _ }) = EvCoercion $ ctEvCoercion ev ctEvTerm ev = EvId (ctEvId ev) ctEvCoercion :: CtEvidence -> Coercion -ctEvCoercion ev@(CtWanted { ctev_dest = HoleDest hole, ctev_pred = pred }) - = case getEqPredTys_maybe pred of - Just (role, ty1, ty2) -> mkHoleCo hole role ty1 ty2 - _ -> pprPanic "ctEvTerm" (ppr ev) -ctEvCoercion (CtGiven { ctev_evar = ev_id }) = mkTcCoVarCo ev_id -ctEvCoercion ev = pprPanic "ctEvCoercion" (ppr ev) +ctEvCoercion (CtGiven { ctev_evar = ev_id }) + = mkTcCoVarCo ev_id +ctEvCoercion (CtWanted { ctev_dest = dest, ctev_pred = pred }) + | HoleDest hole <- dest + , Just (role, ty1, ty2) <- getEqPredTys_maybe pred + = -- ctEvCoercion is only called on type equalities + -- and they always have HoleDests + mkHoleCo hole role ty1 ty2 +ctEvCoercion ev + = pprPanic "ctEvCoercion" (ppr ev) ctEvId :: CtEvidence -> TcId ctEvId (CtWanted { ctev_dest = EvVarDest ev }) = ev From git at git.haskell.org Wed May 3 13:27:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 May 2017 13:27:08 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Shave the hair off mkCastTy. (17ce3c7) Message-ID: <20170503132708.340873A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/17ce3c7ce7f76cd502e970ff313e5b62569282c3/ghc >--------------------------------------------------------------- commit 17ce3c7ce7f76cd502e970ff313e5b62569282c3 Author: Richard Eisenberg Date: Fri Apr 7 11:38:37 2017 -0400 Shave the hair off mkCastTy. Previously, mkCastTy went to great lengths to shove casts around. But this doesn't seem to be necessary. However, the reflexivity check currently in mkCastTy is not enough. See the abortive Note [No reflexive casts in types] (cherry picked from commit ef0ff34d462e3780210567a13d58b868ec3399e0) >--------------------------------------------------------------- 17ce3c7ce7f76cd502e970ff313e5b62569282c3 compiler/types/Type.hs | 135 +++++++-------------- .../tests/typecheck/should_fail/T10619.stderr | 4 +- 2 files changed, 46 insertions(+), 93 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 17ce3c7ce7f76cd502e970ff313e5b62569282c3 From git at git.haskell.org Wed May 3 13:27:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 May 2017 13:27:05 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Use mkCastTy in subst_ty. (769bb2d) Message-ID: <20170503132705.624AD3A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/769bb2d1ce8885e4fa7c8151f5a2840770e628f8/ghc >--------------------------------------------------------------- commit 769bb2d1ce8885e4fa7c8151f5a2840770e628f8 Author: Richard Eisenberg Date: Fri Apr 7 11:39:51 2017 -0400 Use mkCastTy in subst_ty. This allows mkCastTy to maintain invariants. Much like how we use mkAppTy in subst_ty. (cherry picked from commit 466803a0e9628ccd5feb55d062e141e0972fc19c) >--------------------------------------------------------------- 769bb2d1ce8885e4fa7c8151f5a2840770e628f8 compiler/types/TyCoRep.hs | 4 ++-- compiler/types/Type.hs | 11 ----------- compiler/types/Type.hs-boot | 3 ++- 3 files changed, 4 insertions(+), 14 deletions(-) diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index 52a0f1d..300ef80 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -135,7 +135,7 @@ module TyCoRep ( import {-# SOURCE #-} DataCon( dataConFullSig , dataConUnivTyVarBinders, dataConExTyVarBinders , DataCon, filterEqSpec ) -import {-# SOURCE #-} Type( isPredTy, isCoercionTy, mkAppTy +import {-# SOURCE #-} Type( isPredTy, isCoercionTy, mkAppTy, mkCastTy , tyCoVarsOfTypesWellScoped , tyCoVarsOfTypeWellScoped , coreView, typeKind ) @@ -2186,7 +2186,7 @@ subst_ty subst ty (ForAllTy $! ((TvBndr $! tv') vis)) $! (subst_ty subst' ty) go (LitTy n) = LitTy $! n - go (CastTy ty co) = (CastTy $! (go ty)) $! (subst_co subst co) + go (CastTy ty co) = (mkCastTy $! (go ty)) $! (subst_co subst co) go (CoercionTy co) = CoercionTy $! (subst_co subst co) substTyVar :: TCvSubst -> TyVar -> Type diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index 77e4499..2ff78b4 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -1222,10 +1222,6 @@ mkCastTy ty co | isReflexiveCo co = ty mkCastTy (CastTy ty co1) co2 = mkCastTy ty (co1 `mkTransCo` co2) mkCastTy ty co = CastTy ty co -tyConTyBinders :: TyCon -> [TyBinder] --- Return the tyConBinders in TyBinder form -tyConTyBinders tycon = tyConBindersTyBinders (tyConBinders tycon) - tyConBindersTyBinders :: [TyConBinder] -> [TyBinder] -- Return the tyConBinders in TyBinder form tyConBindersTyBinders = map to_tyb @@ -1529,13 +1525,6 @@ caseBinder :: TyBinder -- ^ binder to scrutinize caseBinder (Named v) f _ = f v caseBinder (Anon t) _ d = d t --- | Create a TCvSubst combining the binders and types provided. --- NB: It is specifically OK if the lists are of different lengths. --- Barely used -zipTyBinderSubst :: [TyBinder] -> [Type] -> TCvSubst -zipTyBinderSubst bndrs tys - = mkTvSubstPrs [ (tv, ty) | (Named (TvBndr tv _), ty) <- zip bndrs tys ] - -- | Manufacture a new 'TyConBinder' from a 'TyBinder'. Anonymous -- 'TyBinder's are still assigned names as 'TyConBinder's, so we need -- the extra gunk with which to construct a 'Name'. Used when producing diff --git a/compiler/types/Type.hs-boot b/compiler/types/Type.hs-boot index be7e4ed..2fc251a 100644 --- a/compiler/types/Type.hs-boot +++ b/compiler/types/Type.hs-boot @@ -3,13 +3,14 @@ module Type where import TyCon import Var ( TyVar ) -import {-# SOURCE #-} TyCoRep( Type, Kind ) +import {-# SOURCE #-} TyCoRep( Type, Coercion, Kind ) import Util isPredTy :: Type -> Bool isCoercionTy :: Type -> Bool mkAppTy :: Type -> Type -> Type +mkCastTy :: Type -> Coercion -> Type piResultTy :: Type -> Type -> Type typeKind :: Type -> Kind From git at git.haskell.org Wed May 3 13:27:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 May 2017 13:27:11 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix #13333 by fixing the covar's type in ctEvCoercion (51d80c3) Message-ID: <20170503132711.854C83A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/51d80c3b2c4c7d8f1f5dbcee39864c2de49143c7/ghc >--------------------------------------------------------------- commit 51d80c3b2c4c7d8f1f5dbcee39864c2de49143c7 Author: Richard Eisenberg Date: Sun Apr 23 10:24:30 2017 -0400 Fix #13333 by fixing the covar's type in ctEvCoercion The change is noted in Note [Given in ctEvCoercion]. This patch also adds a bit more commentary to TcFlatten, documenting some key invariants of the flattening algorithm. While in the area, I also removed some stale commentary from TcCanonical. (cherry picked from commit 09bf135ace55ce2572bf4168124d631e386c64bb) >--------------------------------------------------------------- 51d80c3b2c4c7d8f1f5dbcee39864c2de49143c7 compiler/typecheck/TcCanonical.hs | 98 ++++------------------ compiler/typecheck/TcFlatten.hs | 88 +++++++++++++++++-- compiler/typecheck/TcRnTypes.hs | 21 +++-- compiler/typecheck/TcSMonad.hs | 1 + testsuite/tests/typecheck/should_compile/T13333.hs | 28 +++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 6 files changed, 143 insertions(+), 94 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 51d80c3b2c4c7d8f1f5dbcee39864c2de49143c7 From git at git.haskell.org Wed May 3 13:27:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 May 2017 13:27:14 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix #13233 by checking for lev-poly primops (add8e7f) Message-ID: <20170503132714.ACB463A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/add8e7f759e64ff3f9855073d67b1eb3c8f4d83b/ghc >--------------------------------------------------------------- commit add8e7f759e64ff3f9855073d67b1eb3c8f4d83b Author: Richard Eisenberg Date: Sun Apr 23 14:16:32 2017 -0400 Fix #13233 by checking for lev-poly primops The implementation plan is all in Note [Detecting forced eta expansion] in DsExpr. (cherry picked from commit 16b0a07e5d0c72c1171359e546d9373442ec0564) >--------------------------------------------------------------- add8e7f759e64ff3f9855073d67b1eb3c8f4d83b testsuite/tests/codeGen/should_fail/T13233.stderr | 24 +++++++++++++++++++++++ 1 file changed, 24 insertions(+) diff --git a/testsuite/tests/codeGen/should_fail/T13233.stderr b/testsuite/tests/codeGen/should_fail/T13233.stderr new file mode 100644 index 0000000..c1cbb97 --- /dev/null +++ b/testsuite/tests/codeGen/should_fail/T13233.stderr @@ -0,0 +1,24 @@ + +T13233.hs:14:11: error: + Cannot use primitive with levity-polymorphic arguments: + GHC.Prim.(#,#) :: a -> a -> (# a, a #) + Levity-polymorphic arguments: + a :: TYPE rep + a :: TYPE rep + +T13233.hs:22:16: error: + Cannot use primitive with levity-polymorphic arguments: + GHC.Prim.(#,#) :: forall (a :: TYPE rep1) (b :: TYPE rep2). + a -> b -> (# a, b #) + Levity-polymorphic arguments: + a :: TYPE rep1 + b :: TYPE rep2 + +T13233.hs:27:10: error: + Cannot use primitive with levity-polymorphic arguments: + mkWeak# :: a + -> b + -> (State# RealWorld -> (# State# RealWorld, c #)) + -> State# RealWorld + -> (# State# RealWorld, Weak# b #) + Levity-polymorphic arguments: a :: TYPE rep From git at git.haskell.org Wed May 3 13:27:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 May 2017 13:27:18 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Test #13585 in typecheck/should_compile/T13585 (7f36baf) Message-ID: <20170503132718.322433A589@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/7f36baf0646ceeef8207cc5bdb7dae3a54f9c1f0/ghc >--------------------------------------------------------------- commit 7f36baf0646ceeef8207cc5bdb7dae3a54f9c1f0 Author: Richard Eisenberg Date: Mon May 1 23:16:20 2017 -0400 Test #13585 in typecheck/should_compile/T13585 (cherry picked from commit 6df8bef054db0b95bb8f9e55bb82580e27d251d6) >--------------------------------------------------------------- 7f36baf0646ceeef8207cc5bdb7dae3a54f9c1f0 testsuite/tests/typecheck/should_compile/Makefile | 6 ++ testsuite/tests/typecheck/should_compile/T13585.hs | 5 ++ .../tests/typecheck/should_compile/T13585a.hs | 81 ++++++++++++++++++++++ .../tests/typecheck/should_compile/T13585b.hs | 7 ++ testsuite/tests/typecheck/should_compile/all.T | 1 + 5 files changed, 100 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/Makefile b/testsuite/tests/typecheck/should_compile/Makefile index cb8269a..fc90899 100644 --- a/testsuite/tests/typecheck/should_compile/Makefile +++ b/testsuite/tests/typecheck/should_compile/Makefile @@ -56,3 +56,9 @@ Tc271: '$(TEST_HC)' $(TEST_HC_OPTS) -c Tc271.hs-boot '$(TEST_HC)' $(TEST_HC_OPTS) -c Tc271a.hs '$(TEST_HC)' $(TEST_HC_OPTS) -c Tc271.hs + +T13585: + $(RM) -f T13585a.o T13585a.hi T13585b.o T13585b.hi T13585.o T13585.hi + '$(TEST_HC)' $(TEST_HC_OPTS) -c T13585a.hs -O + '$(TEST_HC)' $(TEST_HC_OPTS) -c T13585b.hs -O + '$(TEST_HC)' $(TEST_HC_OPTS) -c T13585.hs -O diff --git a/testsuite/tests/typecheck/should_compile/T13585.hs b/testsuite/tests/typecheck/should_compile/T13585.hs new file mode 100644 index 0000000..74c9412 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13585.hs @@ -0,0 +1,5 @@ +module T13585 where +import T13585b (extractZonedTime) + +main :: IO () +main = print extractZonedTime diff --git a/testsuite/tests/typecheck/should_compile/T13585a.hs b/testsuite/tests/typecheck/should_compile/T13585a.hs new file mode 100644 index 0000000..fda3d70 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13585a.hs @@ -0,0 +1,81 @@ +{-# LANGUAGE KindSignatures, RankNTypes, TypeFamilies, MultiParamTypeClasses, FlexibleInstances,UndecidableInstances #-} + +module T13585a where + +import Data.Monoid (First(..)) +import Data.Functor.Identity + +class Profunctor p where + dimap :: (a -> b) -> (c -> d) -> p b c -> p a d + dimap f g = lmap f . rmap g + {-# INLINE dimap #-} + + lmap :: (a -> b) -> p b c -> p a c + lmap f = dimap f id + {-# INLINE lmap #-} + + rmap :: (b -> c) -> p a b -> p a c + rmap = dimap id + {-# INLINE rmap #-} + + +data Exchange a b s t = Exchange (s -> a) (b -> t) + +instance Functor (Exchange a b s) where + fmap f (Exchange sa bt) = Exchange sa (f . bt) + {-# INLINE fmap #-} + +instance Profunctor (Exchange a b) where + dimap f g (Exchange sa bt) = Exchange (sa . f) (g . bt) + {-# INLINE dimap #-} + lmap f (Exchange sa bt) = Exchange (sa . f) bt + {-# INLINE lmap #-} + rmap f (Exchange sa bt) = Exchange sa (f . bt) + {-# INLINE rmap #-} + + + +withIso :: AnIso s t a b -> ((s -> a) -> (b -> t) -> r) -> r +withIso ai k = case ai (Exchange id Identity) of + Exchange sa bt -> k sa (runIdentity undefined bt) +{-# INLINE withIso #-} + +type Iso s t a b = forall p f. (Profunctor p, Functor f) => p a (f b) -> p s (f t) +type Iso' s a = Iso s s a a +type AnIso s t a b = Exchange a b a (Identity b) -> Exchange a b s (Identity t) + +class (Rewrapped s t, Rewrapped t s) => Rewrapping s t +instance (Rewrapped s t, Rewrapped t s) => Rewrapping s t + + +instance (t ~ First b) => Rewrapped (First a) t +instance Wrapped (First a) where + type Unwrapped (First a) = Maybe a + _Wrapped' = iso getFirst First + {-# INLINE _Wrapped' #-} + +class Wrapped s => Rewrapped (s :: *) (t :: *) + +class Wrapped s where + type Unwrapped s :: * + _Wrapped' :: Iso' s (Unwrapped s) + +_Wrapping :: Rewrapping s t => (Unwrapped s -> s) -> Iso s t (Unwrapped s) (Unwrapped t) +_Wrapping _ = _Wrapped +{-# INLINE _Wrapping #-} + +iso :: (s -> a) -> (b -> t) -> Iso s t a b +iso sa bt = dimap sa (fmap bt) +{-# INLINE iso #-} + +_Wrapped :: Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t) +_Wrapped = withIso _Wrapped' $ \ sa _ -> withIso _Wrapped' $ \ _ bt -> iso sa bt +{-# INLINE _Wrapped #-} + +au :: Functor f => AnIso s t a b -> ((b -> t) -> f s) -> f a +au k = withIso k $ \ sa bt f -> fmap sa (f bt) +{-# INLINE au #-} + +ala :: (Functor f, Rewrapping s t) => (Unwrapped s -> s) -> ((Unwrapped t -> t) -> f s) -> f (Unwrapped s) +ala = au . _Wrapping +{-# INLINE ala #-} diff --git a/testsuite/tests/typecheck/should_compile/T13585b.hs b/testsuite/tests/typecheck/should_compile/T13585b.hs new file mode 100644 index 0000000..db09cf1 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13585b.hs @@ -0,0 +1,7 @@ +module T13585b where + +import T13585a +import Data.Monoid + +extractZonedTime :: Maybe () +extractZonedTime = ala First foldMap [Nothing] diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index acc9de0..ce0b67c 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -552,3 +552,4 @@ test('T13509', normal, compile, ['']) test('T13524', normal, compile, ['']) test('T13603', normal, compile, ['']) test('T13333', normal, compile, ['']) +test('T13585', [extra_files(['T13585.hs', 'T13585a.hs', 'T13585b.hs'])], run_command, ['$MAKE -s --no-print-directory T13585']) From git at git.haskell.org Wed May 3 13:48:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 May 2017 13:48:39 +0000 (UTC) Subject: [commit: ghc] wip/dfeuer-interleave-mvars: Switch to single-MVar unsafeInterleaveIO (aed2d85) Message-ID: <20170503134839.CD95E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/dfeuer-interleave-mvars Link : http://ghc.haskell.org/trac/ghc/changeset/aed2d85f5deacc0e9b0500eb5b1095643e536581/ghc >--------------------------------------------------------------- commit aed2d85f5deacc0e9b0500eb5b1095643e536581 Author: David Feuer Date: Wed May 3 09:47:32 2017 -0400 Switch to single-MVar unsafeInterleaveIO Ben Gamari has pointed out that using two `MVar`s may be reducing efficiency. Let's see what happens with an `MVar . Maybe` approach. The next potential stage is to switch from `Maybe` to null pointers. >--------------------------------------------------------------- aed2d85f5deacc0e9b0500eb5b1095643e536581 libraries/base/GHC/IO/Unsafe.hs | 33 ++++++++++++++++++++++----------- 1 file changed, 22 insertions(+), 11 deletions(-) diff --git a/libraries/base/GHC/IO/Unsafe.hs b/libraries/base/GHC/IO/Unsafe.hs index 5498e19..3c958c1 100644 --- a/libraries/base/GHC/IO/Unsafe.hs +++ b/libraries/base/GHC/IO/Unsafe.hs @@ -112,18 +112,29 @@ file reading, see 'System.IO.hGetContents'. {-# INLINE unsafeInterleaveIO #-} unsafeInterleaveIO :: IO a -> IO a unsafeInterleaveIO m = do - claimedV <- newEmptyMVar - resultV <- newEmptyMVar + v <- newMVar Nothing unsafeDupableInterleaveIO $ do - claimSucceeded <- tryPutMVar claimedV () - if claimSucceeded - then do - -- We were the first ones to claim the computation, so we - -- perform it and store the result. - res <- m - putMVar resultV res - pure res - else readMVar resultV + r <- tryTakeMVar v + case r of + -- Someone else has taken the MVar. By the time they put + -- it back, the action will surely have been performed, + -- so we use the result. + Nothing -> do + res <- readMVar v + case res of + Nothing -> errorWithoutStackTrace "unsafeInterleaveIO: impossible Nothing" + Just a -> pure a + + -- Someone else has performed the action, so we use + -- their result and put it back in the MVar. + Just j@(Just r) -> r <$ putMVar v j + + -- We're the first ones to get the MVar, so we actually + -- do the work. + Just Nothing -> do + res <- m + putMVar v (Just res) + pure res -- Note [unsafeDupableInterleaveIO should not be inlined] From git at git.haskell.org Wed May 3 13:58:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 May 2017 13:58:48 +0000 (UTC) Subject: [commit: ghc] master: Improve fixIO (239418c) Message-ID: <20170503135848.464823A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/239418cf94dede0f116bb859d1bb95891235eb76/ghc >--------------------------------------------------------------- commit 239418cf94dede0f116bb859d1bb95891235eb76 Author: David Feuer Date: Wed May 3 09:57:00 2017 -0400 Improve fixIO Use `unsafeDupableInterleaveIO` to avoid `noDuplicate` calls. Switch from `takeMVar` to `readMVar` as multiple entry with `takeMVar` would lock things up. Reviewers: austin, hvr, bgamari, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3494 >--------------------------------------------------------------- 239418cf94dede0f116bb859d1bb95891235eb76 libraries/base/System/IO.hs | 20 +++++++++++++------- 1 file changed, 13 insertions(+), 7 deletions(-) diff --git a/libraries/base/System/IO.hs b/libraries/base/System/IO.hs index 735d41b..fde5bb6 100644 --- a/libraries/base/System/IO.hs +++ b/libraries/base/System/IO.hs @@ -403,7 +403,7 @@ withBinaryFile name mode = bracket (openBinaryFile name mode) hClose fixIO :: (a -> IO a) -> IO a fixIO k = do m <- newEmptyMVar - ans <- unsafeInterleaveIO (takeMVar m) + ans <- unsafeDupableInterleaveIO (readMVar m) result <- k ans putMVar m result return result @@ -413,12 +413,18 @@ fixIO k = do -- computation a few times before it notices the loop, which is wrong. -- -- NOTE2: the explicit black-holing with an IORef ran into trouble --- with multiple threads (see #5421), so now we use an MVar. I'm --- actually wondering whether we should use readMVar rather than --- takeMVar, just in case it ends up being executed multiple times, --- but even then it would have to be masked to protect against async --- exceptions. Ugh. What we really need here is an IVar, or an --- atomic readMVar, or even STM. All these seem like overkill. +-- with multiple threads (see #5421), so now we use an MVar. We used +-- to use takeMVar with unsafeInterleaveIO. This, however, uses noDuplicate#, +-- which is not particularly cheap. Better to use readMVar, which can be +-- performed in multiple threads safely, and to use unsafeDupableInterleaveIO +-- to avoid the noDuplicate cost. +-- +-- What we'd ideally want is probably an IVar, but we don't quite have those. +-- STM TVars look like an option at first, but I don't think they are: +-- we'd need to be able to write to the variable in an IO context, which can +-- only be done using 'atomically', and 'atomically' is not allowed within +-- unsafePerformIO. We can't know if someone will try to use the result +-- of fixIO with unsafePerformIO! -- -- See also System.IO.Unsafe.unsafeFixIO. -- From git at git.haskell.org Wed May 3 16:42:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 May 2017 16:42:44 +0000 (UTC) Subject: [commit: ghc] branch 'wip/dfeuer-interleave-null' created Message-ID: <20170503164244.8262A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/dfeuer-interleave-null Referencing: a53064ee44d398ba175fdca3bec551e7db62aa26 From git at git.haskell.org Wed May 3 16:42:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 May 2017 16:42:47 +0000 (UTC) Subject: [commit: ghc] wip/dfeuer-interleave-null: Speed up unsafeInterleaveIO (a53064e) Message-ID: <20170503164247.4E8513A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/dfeuer-interleave-null Link : http://ghc.haskell.org/trac/ghc/changeset/a53064ee44d398ba175fdca3bec551e7db62aa26/ghc >--------------------------------------------------------------- commit a53064ee44d398ba175fdca3bec551e7db62aa26 Author: David Feuer Date: Tue May 2 17:09:00 2017 -0400 Speed up unsafeInterleaveIO Summary: Use an `MVar` and a "null pointer" trick I learned from Edward Kmett to try to make `unsafeInterleaveIO` faster in the threaded runtime, where `noDuplicate#` is not always cheap. Reviewers: austin, hvr, bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3529 >--------------------------------------------------------------- a53064ee44d398ba175fdca3bec551e7db62aa26 libraries/base/GHC/IO/Unsafe.hs | 29 ++++++++++++++++++++++++++--- 1 file changed, 26 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/IO/Unsafe.hs b/libraries/base/GHC/IO/Unsafe.hs index c1c07ae..376412b 100644 --- a/libraries/base/GHC/IO/Unsafe.hs +++ b/libraries/base/GHC/IO/Unsafe.hs @@ -26,7 +26,9 @@ module GHC.IO.Unsafe ( ) where import GHC.Base - +import GHC.MVar +import GHC.IORef +import GHC.STRef {-| This is the \"back door\" into the 'IO' monad, allowing @@ -111,12 +113,33 @@ file reading, see 'System.IO.hGetContents'. -} {-# INLINE unsafeInterleaveIO #-} unsafeInterleaveIO :: IO a -> IO a -unsafeInterleaveIO m = unsafeDupableInterleaveIO (noDuplicate >> m) +unsafeInterleaveIO m = do + v <- case unclaimed of + IORef (STRef r) -> unsafeCoerce# newMVar r + unsafeDupableInterleaveIO $ do + a <- takeMVar v + if isUnclaimed a + then do + res <- m + putMVar v res + pure res + else a <$ putMVar v a + +-- We use 'unclaimed' as a "null pointer" in 'unsafeInterleaveIO'. +-- It must not be exported! +{-# NOINLINE unclaimed #-} +unclaimed :: IORef () +unclaimed = unsafePerformIO $ newIORef () + +isUnclaimed :: a -> Bool +isUnclaimed a = case unclaimed of + IORef (STRef r) -> isTrue# (unsafeCoerce# reallyUnsafePtrEquality# a r) + -- Note [unsafeDupableInterleaveIO should not be inlined] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -- --- We used to believe that INLINE on unsafeInterleaveIO was safe, +-- We used to believe that INLINE on unsafeDupableInterleaveIO was safe, -- because the state from this IO thread is passed explicitly to the -- interleaved IO, so it cannot be floated out and shared. -- From git at git.haskell.org Wed May 3 18:36:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 May 2017 18:36:01 +0000 (UTC) Subject: [commit: ghc] wip/dfeuer-interleave-null: Speed up unsafeInterleaveIO (f2851e1) Message-ID: <20170503183601.1C2BB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/dfeuer-interleave-null Link : http://ghc.haskell.org/trac/ghc/changeset/f2851e13ae66a38dedec6d7c59aca3fe99bfb817/ghc >--------------------------------------------------------------- commit f2851e13ae66a38dedec6d7c59aca3fe99bfb817 Author: David Feuer Date: Tue May 2 17:09:00 2017 -0400 Speed up unsafeInterleaveIO Summary: Use an `MVar` and a "null pointer" trick I learned from Edward Kmett to try to make `unsafeInterleaveIO` faster in the threaded runtime, where `noDuplicate#` is not always cheap. Reviewers: austin, hvr, bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3529 >--------------------------------------------------------------- f2851e13ae66a38dedec6d7c59aca3fe99bfb817 libraries/base/GHC/IO/Unsafe.hs | 77 +++++++++++++++++++++++++++++++++++++++-- 1 file changed, 74 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/IO/Unsafe.hs b/libraries/base/GHC/IO/Unsafe.hs index c1c07ae..698b9fd 100644 --- a/libraries/base/GHC/IO/Unsafe.hs +++ b/libraries/base/GHC/IO/Unsafe.hs @@ -26,7 +26,7 @@ module GHC.IO.Unsafe ( ) where import GHC.Base - +import GHC.MVar {-| This is the \"back door\" into the 'IO' monad, allowing @@ -111,12 +111,83 @@ file reading, see 'System.IO.hGetContents'. -} {-# INLINE unsafeInterleaveIO #-} unsafeInterleaveIO :: IO a -> IO a -unsafeInterleaveIO m = unsafeDupableInterleaveIO (noDuplicate >> m) +-- See Note [Null pointers in unsafeInterleaveIO] +unsafeInterleaveIO m = do + v <- case unclaimed of + Box r -> unsafeCoerce# newMVar r + unsafeDupableInterleaveIO $ do + a <- takeMVar v + if isUnclaimed a + then do + res <- m + putMVar v res + pure res + else a <$ putMVar v a + +-- The 'Unclaimed' constructor must not be exported. +data Unclaimed = Unclaimed +data Box = Box !Unclaimed + +-- We use 'unclaimed' as a "null pointer" in 'unsafeInterleaveIO'. +-- It must not be exported! +-- See Note [Null pointers in unsafeInterleaveIO] +{-# NOINLINE unclaimed #-} +unclaimed :: Box +unclaimed = Box Unclaimed + +isUnclaimed :: a -> Bool +isUnclaimed a = case unclaimed of + Box r -> isTrue# (unsafeCoerce# reallyUnsafePtrEquality# a r) + +-- Note [Null pointers in unsafeInterleaveIO] +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- +-- Conceptually, we're implementing this: +-- +-- unsafeInterleaveIO :: IO a -> IO a +-- unsafeInterleaveIO m = do +-- v <- newMVar Nothing +-- unsafeDupableInterleaveIO $ do +-- r <- takeMVar v +-- case r of +-- -- We're the first ones to get the MVar, so we actually +-- -- do the work. +-- Nothing -> do +-- a <- m +-- putMVar v (Just a) +-- pure a +-- +-- -- Someone else has claimed the action, so we use +-- -- their result and put it back in the MVar. +-- j@(Just a) -> a <$ putMVar v j +-- +-- The MVar starts out full, with Nothing in it. When the interleaved +-- computation is complete, the result will be stored in the MVar in a Just +-- constructor. The interleaved computation, which may run in multiple +-- threads, takes the MVar, checks whether it's Nothing or Just, and either +-- performs the interleaved computation or just puts the Just back. +-- +-- However, allocating Just constructors is wasteful; we can pretend we're +-- writing in C and use a distinguished "null pointer" to represent Nothing +-- instead. We magic up a single, global null pointer and use that every time. +-- The usual problem with null pointers is that they can't distinguish, among +-- Nothing, Just Nothing, Just (Just Nothing), etc. Fortunately, we don't have +-- to worry about that here. The null pointer is private to this module, so +-- it is impossible for the computation passed to 'unsafeInterleaveIO' to +-- produce it. +-- +-- Why do we have to build a box around the distinguished null? I don't +-- actually know. But without this box, 'reallyUnsafePtrEquality#' does not +-- seem to detect equality! Note that we rely on the fact that GHC uses +-- distinct heap locations to represent nullary constructors of distinct +-- datatypes. If this changes, we can recover the correct behavior by using +-- 'unsafePerformIO' to allocate something like an 'IORef' and use the +-- embedded 'MutVar#' as a null pointer. -- Note [unsafeDupableInterleaveIO should not be inlined] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -- --- We used to believe that INLINE on unsafeInterleaveIO was safe, +-- We used to believe that INLINE on unsafeDupableInterleaveIO was safe, -- because the state from this IO thread is passed explicitly to the -- interleaved IO, so it cannot be floated out and shared. -- From git at git.haskell.org Thu May 4 13:35:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 13:35:01 +0000 (UTC) Subject: [commit: ghc] master: Teach optCoecion about FunCo (783dfa7) Message-ID: <20170504133501.1524C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/783dfa744b14e682951a8358e51356a2dedda325/ghc >--------------------------------------------------------------- commit 783dfa744b14e682951a8358e51356a2dedda325 Author: Simon Peyton Jones Date: Tue May 2 16:30:38 2017 +0100 Teach optCoecion about FunCo I was seeing coercions like Nth 3 ((c2 -> c2) ; (c3 -> c4)) which made me realise that optCoercion was doing a bad job of the (relatively new) FunCo. In particular, opt_trans_rule needs a FunCo/FunCo case, to go with the TyConAppCo/TyConAppCo case. Easy. No behavioural change, some coercions will get smaller >--------------------------------------------------------------- 783dfa744b14e682951a8358e51356a2dedda325 compiler/types/OptCoercion.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/compiler/types/OptCoercion.hs b/compiler/types/OptCoercion.hs index 7f96754..b1aa646 100644 --- a/compiler/types/OptCoercion.hs +++ b/compiler/types/OptCoercion.hs @@ -555,6 +555,11 @@ opt_trans_rule is in_co1@(TyConAppCo r1 tc1 cos1) in_co2@(TyConAppCo r2 tc2 cos2 fireTransRule "PushTyConApp" in_co1 in_co2 $ mkTyConAppCo r1 tc1 (opt_transList is cos1 cos2) +opt_trans_rule is in_co1@(FunCo r1 co1a co1b) in_co2@(FunCo r2 co2a co2b) + = ASSERT( r1 == r2 ) -- Just like the TyConAppCo/TyConAppCo case + fireTransRule "PushFun" in_co1 in_co2 $ + mkFunCo r1 (opt_trans is co1a co2a) (opt_trans is co1b co2b) + opt_trans_rule is in_co1@(AppCo co1a co1b) in_co2@(AppCo co2a co2b) = fireTransRule "TrPushApp" in_co1 in_co2 $ mkAppCo (opt_trans is co1a co2a) From git at git.haskell.org Thu May 4 14:21:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 14:21:21 +0000 (UTC) Subject: [commit: ghc] master: Abandon typedefing the {Section, ObjectCode}FormatInfo structs (81af480) Message-ID: <20170504142121.9D7EE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/81af480a0fd3b37fff17245c1468638597261bcb/ghc >--------------------------------------------------------------- commit 81af480a0fd3b37fff17245c1468638597261bcb Author: Gabor Greif Date: Wed May 3 11:07:10 2017 +0200 Abandon typedefing the {Section,ObjectCode}FormatInfo structs Summary: This is a follow-up to @angerman 's refactoring for ELF that happened with e5e8646d3c6af82549b55fbee6764b087144a7ec My previous commit a6675a93efe7cae2f206508047a39e73ce4e92a5 corrected a typedef redefinition issue with GCC v4.4 (which is pervasive with RHEL 6). Now the problem has resurfaced. Instead of dancing after the different compiler's pipe, I decided to eliminate the typedefs altogether and refer to the struct namespace explicitly. Added a note to describe why typedefs are not applied on customisable structs. Reviewers: austin, bgamari, erikd, simonmar Subscribers: rwbarton, thomie, angerman Differential Revision: https://phabricator.haskell.org/D3527 >--------------------------------------------------------------- 81af480a0fd3b37fff17245c1468638597261bcb rts/Linker.c | 2 +- rts/LinkerInternals.h | 31 ++++++++++++++++++++++--------- rts/linker/Elf.c | 4 ++-- rts/linker/ElfTypes.h | 9 ++++----- rts/linker/MachOTypes.h | 8 ++++---- 5 files changed, 33 insertions(+), 21 deletions(-) diff --git a/rts/Linker.c b/rts/Linker.c index f1ba84a..65caf89 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -1766,7 +1766,7 @@ addSection (Section *s, SectionKind kind, SectionAlloc alloc, s->mapped_start = mapped_start; /* start of mmap() block */ s->mapped_size = mapped_size; /* size of mmap() block */ - s->info = (SectionFormatInfo*)stgCallocBytes(1, sizeof(SectionFormatInfo), + s->info = (struct SectionFormatInfo*)stgCallocBytes(1, sizeof *s->info, "addSection(SectionFormatInfo)"); IF_DEBUG(linker, diff --git a/rts/LinkerInternals.h b/rts/LinkerInternals.h index 4574f39..a884561 100644 --- a/rts/LinkerInternals.h +++ b/rts/LinkerInternals.h @@ -20,9 +20,6 @@ typedef void SymbolAddr; typedef char SymbolName; -typedef struct _SectionFormatInfo SectionFormatInfo; -typedef struct _ObjectCodeFormatInfo ObjectCodeFormatInfo; - /* See Linker.c Note [runtime-linker-phases] */ typedef enum { OBJECT_LOADED, @@ -52,6 +49,18 @@ typedef } SectionAlloc; +/* + * Note [No typedefs for customizable types] + * Some pointer-to-struct types are defined opaquely + * first, and customized later to architecture/ABI-specific + * instantiations. Having the usual + * typedef struct _Foo {...} Foo; + * wrappers is hard to get right with older versions of GCC, + * so just have a + * struct Foo {...}; + * and always refer to it with the 'struct' qualifier. + */ + typedef struct _Section { void* start; /* actual start of section in memory */ @@ -66,8 +75,10 @@ typedef void* mapped_start; /* start of mmap() block */ StgWord mapped_size; /* size of mmap() block */ - /* A customizable type to augment the Section type. */ - SectionFormatInfo* info; + /* A customizable type to augment the Section type. + * See Note [No typedefs for customizable types] + */ + struct SectionFormatInfo* info; } Section; @@ -142,8 +153,10 @@ typedef struct _ObjectCode { /* ptr to mem containing the object file image */ char* image; - /* A customizable type, that formats can use to augment ObjectCode */ - ObjectCodeFormatInfo *info; + /* A customizable type, that formats can use to augment ObjectCode + * See Note [No typedefs for customizable types] + */ + struct ObjectCodeFormatInfo* info; /* non-zero if the object file was mmap'd, otherwise malloc'd */ int imageMapped; @@ -321,8 +334,8 @@ char *cstring_from_section_name( # include "linker/ElfTypes.h" #elif defined (mingw32_HOST_OS) # define OBJFORMAT_PEi386 -struct _SectionFormatInfo { void* placeholder; }; -struct _ObjectCodeFormatInfo { void* placeholder; }; +struct SectionFormatInfo { void* placeholder; }; +struct ObjectCodeFormatInfo { void* placeholder; }; #elif defined(darwin_HOST_OS) || defined(ios_HOST_OS) # define OBJFORMAT_MACHO # include "linker/MachOTypes.h" diff --git a/rts/linker/Elf.c b/rts/linker/Elf.c index c1caf9a..da3e7c6 100644 --- a/rts/linker/Elf.c +++ b/rts/linker/Elf.c @@ -161,8 +161,8 @@ get_shndx_table(Elf_Ehdr* ehdr) void ocInit_ELF(ObjectCode * oc) { - oc->info = (ObjectCodeFormatInfo*)stgCallocBytes( - 1, sizeof(ObjectCodeFormatInfo), + oc->info = (struct ObjectCodeFormatInfo*)stgCallocBytes( + 1, sizeof *oc->info, "ocInit_Elf(ObjectCodeFormatInfo)"); // TODO: fill info oc->info->elfHeader = (Elf_Ehdr *)oc->image; diff --git a/rts/linker/ElfTypes.h b/rts/linker/ElfTypes.h index a9f4a02..2f34d4a 100644 --- a/rts/linker/ElfTypes.h +++ b/rts/linker/ElfTypes.h @@ -130,7 +130,7 @@ typedef struct _ElfRelocationATable { * Header provides Information about the sections. * */ -typedef struct _ObjectCodeFormatInfo { +struct ObjectCodeFormatInfo { Elf_Ehdr *elfHeader; Elf_Phdr *programHeader; Elf_Shdr *sectionHeader; @@ -144,8 +144,7 @@ typedef struct _ObjectCodeFormatInfo { /* pointer to the global offset table */ void * got_start; size_t got_size; - -} ObjectCodeFormatInfo; +}; typedef struct _Stub { @@ -154,7 +153,7 @@ struct _Stub { struct _Stub * next; } Stub; -typedef struct _SectionFormatInfo { +struct SectionFormatInfo { /* * The following fields are relevant for stubs next to sections only. */ @@ -166,6 +165,6 @@ typedef struct _SectionFormatInfo { char * name; Elf_Shdr *sectionHeader; -} SectionFormatInfo; +}; #endif /* OBJECTFORMAT_ELF */ #endif /* ElfTypes_h */ diff --git a/rts/linker/MachOTypes.h b/rts/linker/MachOTypes.h index b7ee7e2..7d9d64c 100644 --- a/rts/linker/MachOTypes.h +++ b/rts/linker/MachOTypes.h @@ -38,7 +38,7 @@ typedef struct _MachOSymbol { MachONList * nlist; /* the nlist symbol entry */ } MachOSymbol; -typedef struct _ObjectCodeFormatInfo { +struct ObjectCodeFormatInfo { // while we have the image // we can store some pointers // into it, so we don't have @@ -63,7 +63,7 @@ typedef struct _ObjectCodeFormatInfo { /* pointer to the global offset table */ void *got_start; size_t got_size; -} ObjectCodeFormatInfo; +}; /* When loading sections of the macho * into different pages, such that the @@ -112,7 +112,7 @@ struct _Stub { } Stub; -typedef struct _SectionFormatInfo { +struct SectionFormatInfo { /* * The following fields are relevant for stubs next to sections only. */ @@ -126,6 +126,6 @@ typedef struct _SectionFormatInfo { */ MachOSection * macho_section; MachORelocationInfo * relocation_info; -} SectionFormatInfo; +}; #endif /* OBJECTFORMAT_MACHO */ From git at git.haskell.org Thu May 4 16:27:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 16:27:31 +0000 (UTC) Subject: [commit: ghc] master: Deal with exceptions in dsWhenNoErrs (e770197) Message-ID: <20170504162731.CDA283A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e77019767fe5327011c6dc8fe089c64884120aab/ghc >--------------------------------------------------------------- commit e77019767fe5327011c6dc8fe089c64884120aab Author: Simon Peyton Jones Date: Thu May 4 13:33:04 2017 +0100 Deal with exceptions in dsWhenNoErrs Gracious me. Ever since this patch commit 374457809de343f409fbeea0a885877947a133a2 Author: Jan Stolarek Date: Fri Jul 11 13:54:45 2014 +0200 Injective type families TcRnMonad.askNoErrs has been wrong. It looked like this askNoErrs :: TcRn a -> TcRn (a, Bool) askNoErrs m = do { errs_var <- newTcRef emptyMessages ; res <- setErrsVar errs_var m ; (warns, errs) <- readTcRef errs_var ; addMessages (warns, errs) ; return (res, isEmptyBag errs) } The trouble comes if 'm' throws an exception in the TcRn monad. Then 'errs_var is never read, so any errors are simply lost. This mistake was then propgated into DsMonad.dsWhenNoErrs, where it gave rise to Trac #13642. Thank to Ryan for narrowing it down so sharply. I did some refactoring, as usual. >--------------------------------------------------------------- e77019767fe5327011c6dc8fe089c64884120aab compiler/deSugar/DsMonad.hs | 32 +++++++++--- compiler/ghci/RtClosureInspect.hs | 10 ++-- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcRnMonad.hs | 102 +++++++++++++++++++------------------- compiler/typecheck/TcSplice.hs | 8 +-- testsuite/tests/th/T13642.hs | 9 ++++ testsuite/tests/th/T13642.stderr | 4 ++ testsuite/tests/th/all.T | 1 + 8 files changed, 94 insertions(+), 74 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 e77019767fe5327011c6dc8fe089c64884120aab From git at git.haskell.org Thu May 4 16:27:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 16:27:28 +0000 (UTC) Subject: [commit: ghc] master: Comments only, about Typeable/TypeRep/KindRep (2a09700) Message-ID: <20170504162728.090BB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2a09700149732df529cfcb506932c524e7851b4a/ghc >--------------------------------------------------------------- commit 2a09700149732df529cfcb506932c524e7851b4a Author: Simon Peyton Jones Date: Thu May 4 17:26:41 2017 +0100 Comments only, about Typeable/TypeRep/KindRep >--------------------------------------------------------------- 2a09700149732df529cfcb506932c524e7851b4a compiler/typecheck/TcTypeable.hs | 55 ++++++++++++++++++++++------------------ compiler/types/TyCon.hs | 5 +++- libraries/ghc-prim/GHC/Types.hs | 2 +- 3 files changed, 35 insertions(+), 27 deletions(-) diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index d30a722..4c6076e 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -72,7 +72,7 @@ The overall plan is this: Here 0# is the number of arguments expected by the tycon to fully determine its kind. kind_rep is a value of type GHC.Types.KindRep, which gives a recipe for computing the kind of an instantiation of the tycon (see - Note [Representing TyCon kinds] later in this file for details). + Note [Representing TyCon kinds: KindRep] later in this file for details). We define (in TyCon) @@ -640,54 +640,59 @@ word64 dflags n | otherwise = HsWordPrim NoSourceText (toInteger n) {- -Note [Representing TyCon kinds] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ - +Note [Representing TyCon kinds: KindRep] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ One of the operations supported by Typeable is typeRepKind, typeRepKind :: TypeRep (a :: k) -> TypeRep k -Implementing this is a bit tricky. To see why let's consider the TypeRep -encoding of `Proxy Int` where +Implementing this is a bit tricky for poly-kinded types like data Proxy (a :: k) :: Type + -- Proxy :: forall k. k -> Type -which looks like, +The TypeRep encoding of `Proxy Type Int` looks like this: - $tcProxy :: TyCon + $tcProxy :: GHC.Types.TyCon $trInt :: TypeRep Int $trType :: TypeRep Type - $trProxyType :: TypeRep (Proxy :: Type -> Type) + $trProxyType :: TypeRep (Proxy Type :: Type -> Type) $trProxyType = TrTyCon $tcProxy [$trType] -- kind variable instantiation - $trProxy :: TypeRep (Proxy Int) + $trProxy :: TypeRep (Proxy Type Int) $trProxy = TrApp $trProxyType $trInt -Note how $trProxyType encodes only the kind variables of the TyCon -instantiation. To compute the kind (Proxy Int) we need to have a recipe to -compute the kind of a concrete instantiation of Proxy. We call this recipe a -KindRep and store it in the TyCon produced for Proxy, + $tkProxy :: GHC.Types.KindRep + $tkProxy = KindRepFun (KindRepVar 0) (KindRepTyConApp $trType []) - type KindBndr = Int -- de Bruijn index +Note how $trProxyType cannot use 'TrApp', because TypeRep cannot represent +polymorphic types. So instead - data KindRep = KindRepTyConApp TyCon [KindRep] - | KindRepVar !KindBndr - | KindRepApp KindRep KindRep - | KindRepFun KindRep KindRep + * $trProxyType uses 'TrTyCon' to apply Proxy to (the representations) + of all its kind arguments. We can't represent a tycon that is + applied to only some of its kind arguments. -The KindRep for Proxy would look like, + * In $tcProxy, the GHC.Types.TyCon structure for Proxy, we store a + GHC.Types.KindRep, which represents the polymorphic kind of Proxy + Proxy :: forall k. k->Type - $tkProxy :: KindRep - $tkProxy = KindRepFun (KindRepVar 0) (KindRepTyConApp $trType []) + * A KindRep is just a recipe that we can instantiate with the + argument kinds, using Data.Typeable.Internal.instantiateKindRep. + Data.Typeable.Internal.typeRepKind uses instantiateKindRep -data Maybe a = Nothing | Just a + * In a KindRep, the kind variables are represented by 0-indexed + de Bruijn numbers: -'Just :: a -> Maybe a + type KindBndr = Int -- de Bruijn index -F :: forall k. k -> forall k'. k' -> Type + data KindRep = KindRepTyConApp TyCon [KindRep] + | KindRepVar !KindBndr + | KindRepApp KindRep KindRep + | KindRepFun KindRep KindRep + ... -} mkList :: Type -> [LHsExpr Id] -> LHsExpr Id diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index 99a20af..9f6486b 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -403,6 +403,9 @@ tyConBinderArgFlag (TvBndr _ (NamedTCB vis)) = vis tyConBinderArgFlag (TvBndr _ AnonTCB) = Required isNamedTyConBinder :: TyConBinder -> Bool +-- Identifies kind variables +-- E.g. data T k (a:k) = blah +-- Here 'k' is a NamedTCB, a variable used in the kind of other binders isNamedTyConBinder (TvBndr _ (NamedTCB {})) = True isNamedTyConBinder _ = False @@ -427,7 +430,7 @@ mkTyConKind bndrs res_kind = foldr mk res_kind bndrs All TyCons have this group of fields tyConBinders :: [TyConBinder] tyConResKind :: Kind - tyConTyVars :: [TyVra] -- Cached = binderVars tyConBinders + tyConTyVars :: [TyVar] -- Cached = binderVars tyConBinders tyConKind :: Kind -- Cached = mkTyConKind tyConBinders tyConResKind tyConArity :: Arity -- Cached = length tyConBinders diff --git a/libraries/ghc-prim/GHC/Types.hs b/libraries/ghc-prim/GHC/Types.hs index a4b7a91..3756c58 100644 --- a/libraries/ghc-prim/GHC/Types.hs +++ b/libraries/ghc-prim/GHC/Types.hs @@ -450,7 +450,7 @@ type KindBndr = Int #endif -- | The representation produced by GHC for conjuring up the kind of a --- 'TypeRep'. +-- 'TypeRep'. See Note [Representing TyCon kinds: KindRep] in TcTypeable. data KindRep = KindRepTyConApp TyCon [KindRep] | KindRepVar !KindBndr | KindRepApp KindRep KindRep From git at git.haskell.org Thu May 4 16:27:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 16:27:34 +0000 (UTC) Subject: [commit: ghc] master: Remove unused import (2a33f17) Message-ID: <20170504162734.846BA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2a33f172cc7788020822b7a1d022af9348997396/ghc >--------------------------------------------------------------- commit 2a33f172cc7788020822b7a1d022af9348997396 Author: Simon Peyton Jones Date: Thu May 4 13:38:24 2017 +0100 Remove unused import >--------------------------------------------------------------- 2a33f172cc7788020822b7a1d022af9348997396 compiler/vectorise/Vectorise/Monad.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/compiler/vectorise/Vectorise/Monad.hs b/compiler/vectorise/Vectorise/Monad.hs index b49e8d5..ac8b87a 100644 --- a/compiler/vectorise/Vectorise/Monad.hs +++ b/compiler/vectorise/Vectorise/Monad.hs @@ -31,7 +31,6 @@ import TcRnMonad import DsMonad import HscTypes hiding ( MonadThings(..) ) import DynFlags -import MonadUtils (liftIO) import InstEnv import Class import TyCon From git at git.haskell.org Thu May 4 17:18:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 17:18:05 +0000 (UTC) Subject: [commit: ghc] master: Add test for #13320 (cb850e0) Message-ID: <20170504171805.0C0603A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cb850e01560adf12e83fcf85f479636be17d017c/ghc >--------------------------------------------------------------- commit cb850e01560adf12e83fcf85f479636be17d017c Author: David Feuer Date: Thu May 4 13:17:34 2017 -0400 Add test for #13320 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13320 Differential Revision: https://phabricator.haskell.org/D3532 >--------------------------------------------------------------- cb850e01560adf12e83fcf85f479636be17d017c testsuite/tests/typecheck/should_fail/T13320.hs | 32 ++++++++++++++++++++++ .../tests/typecheck/should_fail/T13320.stderr | 8 ++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 41 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T13320.hs b/testsuite/tests/typecheck/should_fail/T13320.hs new file mode 100644 index 0000000..d80dd4f --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T13320.hs @@ -0,0 +1,32 @@ +{-# language ConstraintKinds, FlexibleContexts, TypeFamilies, + UndecidableInstances, DeriveFunctor #-} + +module T13320 where + +import GHC.Exts (Constraint) + +data QCGen + +newtype Gen a = MkGen { unGen :: QCGen -> Int -> a } + deriving Functor + +sized :: (Int -> Gen a) -> Gen a +sized f = MkGen (\r n -> let MkGen m = f n in m r n) + +class Arbitrary a where + arbitrary :: Gen a + +type family X_Var ξ + +data TermX ξ = Var (X_Var ξ) + +type ForallX (φ :: * -> Constraint) ξ = ( φ (X_Var ξ) ) + +-- This type signature used to be necessary to prevent the +-- type checker from looping. +-- genTerm :: ForallX Arbitrary ξ => Int -> Gen (TermX ξ) +genTerm 0 = Var <$> arbitrary +genTerm n = Var <$> genTerm (n - 1) + +instance ForallX Arbitrary ξ => Arbitrary (TermX ξ) where + arbitrary = sized genTerm diff --git a/testsuite/tests/typecheck/should_fail/T13320.stderr b/testsuite/tests/typecheck/should_fail/T13320.stderr new file mode 100644 index 0000000..de783b0 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T13320.stderr @@ -0,0 +1,8 @@ + +T13320.hs:32:21: error: + • Couldn't match expected type ‘TermX ξ’ with actual type ‘X_Var ξ’ + • In the first argument of ‘sized’, namely ‘genTerm’ + In the expression: sized genTerm + In an equation for ‘arbitrary’: arbitrary = sized genTerm + • Relevant bindings include + arbitrary :: Gen (TermX ξ) (bound at T13320.hs:32:3) diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 8bbb671..3aa8cd5 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -435,3 +435,4 @@ test('T12709', normal, compile_fail, ['']) test('T13446', normal, compile_fail, ['']) test('T13506', normal, compile_fail, ['']) test('T13611', expect_broken(13611), compile_fail, ['']) +test('T13320', normal, compile_fail, ['']) From git at git.haskell.org Thu May 4 18:24:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 18:24:16 +0000 (UTC) Subject: [commit: nofib] master: spectral: enable exact-reals (65a247d) Message-ID: <20170504182416.5B0B83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/65a247dff447756ef6ac2c60bf0a6c8a0d9fb2bb/nofib >--------------------------------------------------------------- commit 65a247dff447756ef6ac2c60bf0a6c8a0d9fb2bb Author: Michal Terepeta Date: Thu May 4 08:46:35 2017 -0400 spectral: enable exact-reals The benchmark only needed a small update to the expected stdandard output file (missing newline). Signed-off-by: Michal Terepeta Test Plan: build & run Reviewers: dfeuer, bgamari Reviewed By: dfeuer Differential Revision: https://phabricator.haskell.org/D3363 >--------------------------------------------------------------- 65a247dff447756ef6ac2c60bf0a6c8a0d9fb2bb spectral/Makefile | 7 ++++--- spectral/exact-reals/exact-reals.stdout | 0 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/spectral/Makefile b/spectral/Makefile index 6eb35a5..1a70b28 100644 --- a/spectral/Makefile +++ b/spectral/Makefile @@ -4,9 +4,10 @@ include $(TOP)/mk/boilerplate.mk # TODO(michalt): Re-enable `secretary` (requires `random`) SUBDIRS = ansi atom awards banner boyer boyer2 calendar cichelli circsim \ clausify constraints cryptarithm1 cryptarithm2 cse eliza expert \ - fft2 fibheaps fish gcd hartel integer knights lambda last-piece lcss life \ - mandel mandel2 mate minimax multiplier para power pretty primetest \ - puzzle rewrite scc simple sorting sphere treejoin + exact-reals fft2 fibheaps fish gcd hartel integer knights lambda \ + last-piece lcss life mandel mandel2 mate minimax multiplier para \ + power pretty primetest puzzle rewrite scc simple sorting sphere \ + treejoin include $(TOP)/mk/target.mk From git at git.haskell.org Thu May 4 18:24:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 18:24:18 +0000 (UTC) Subject: [commit: nofib] master: spectral/sphere: simplify Makefile (bdefa19) Message-ID: <20170504182418.67E3E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bdefa193d17314f8637622db81f32c55103ef942/nofib >--------------------------------------------------------------- commit bdefa193d17314f8637622db81f32c55103ef942 Author: Michal Terepeta Date: Thu May 4 08:46:43 2017 -0400 spectral/sphere: simplify Makefile By simply renaming the expected output files to follow the usual conventions, we can simplify the `Makefile` a bit. Signed-off-by: Michal Terepeta Test Plan: build & run Reviewers: bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D3366 >--------------------------------------------------------------- bdefa193d17314f8637622db81f32c55103ef942 spectral/sphere/Makefile | 6 ------ spectral/sphere/{spheres.slowppm => sphere.slowstdout} | 0 spectral/sphere/{spheres.ppm => sphere.stdout} | 0 3 files changed, 6 deletions(-) diff --git a/spectral/sphere/Makefile b/spectral/sphere/Makefile index c735c0d..ae535ed 100644 --- a/spectral/sphere/Makefile +++ b/spectral/sphere/Makefile @@ -4,12 +4,6 @@ FAST_OPTS = 100 NORM_OPTS = 100 SLOW_OPTS = 200 -ifeq "$(mode)" "slow" -SRC_RUNTEST_OPTS += -o1 spheres.slowppm -else -SRC_RUNTEST_OPTS += -o1 spheres.ppm -endif - include $(TOP)/mk/boilerplate.mk include $(TOP)/mk/target.mk diff --git a/spectral/sphere/spheres.slowppm b/spectral/sphere/sphere.slowstdout similarity index 100% rename from spectral/sphere/spheres.slowppm rename to spectral/sphere/sphere.slowstdout diff --git a/spectral/sphere/spheres.ppm b/spectral/sphere/sphere.stdout similarity index 100% rename from spectral/sphere/spheres.ppm rename to spectral/sphere/sphere.stdout From git at git.haskell.org Thu May 4 18:24:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 18:24:20 +0000 (UTC) Subject: [commit: nofib] master: spectral/mate: remove unnecessary HS_SRCS (569d8eb) Message-ID: <20170504182420.719133A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/569d8eb56370cdca0fce4628b2df211627ef137d/nofib >--------------------------------------------------------------- commit 569d8eb56370cdca0fce4628b2df211627ef137d Author: Michal Terepeta Date: Thu May 4 08:46:54 2017 -0400 spectral/mate: remove unnecessary HS_SRCS I've mistakenly added it as a workaround to build problems, but the whole problem was only due a missing `.depend` file (which is created by `make boot` and interestigly is not cleaned by `make clean`). In any way, the `HS_SRCS` is simply unnecessary and can be removed. Signed-off-by: Michal Terepeta Test Plan: build & run Reviewers: bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D3389 >--------------------------------------------------------------- 569d8eb56370cdca0fce4628b2df211627ef137d spectral/mate/Makefile | 4 ---- 1 file changed, 4 deletions(-) diff --git a/spectral/mate/Makefile b/spectral/mate/Makefile index d2812b9..798ed44 100644 --- a/spectral/mate/Makefile +++ b/spectral/mate/Makefile @@ -1,10 +1,6 @@ TOP = ../.. include $(TOP)/mk/boilerplate.mk -# It's necessary to specify those manually so that the current make-based system -# compiles them in the right order. -# TODO(michalt): This should go away once we move to the Shake-based system. -HS_SRCS = Board.hs Move.hs Problem.hs Solution.hs Main.hs PROG_ARGS = holzhausen.prob # Other problems From git at git.haskell.org Thu May 4 18:24:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 18:24:22 +0000 (UTC) Subject: [commit: nofib] master: Create runtime_files directory for some benchmarks (c6b9143) Message-ID: <20170504182422.96DC73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c6b9143332b6171c251d2e72fb6a5484611031fb/nofib >--------------------------------------------------------------- commit c6b9143332b6171c251d2e72fb6a5484611031fb Author: Michal Terepeta Date: Thu May 4 08:47:03 2017 -0400 Create runtime_files directory for some benchmarks Summary: This creates `runtime_files` subdirectory for benchmarks that need some files at runtime. This make it clear what files are actually needed to run the benchmarks and makes it much easier to support building/running them out of separate build directory. This affects the following benchmarks: - real/anna - real/cacheprof - real/fluid - real/hidden - real/maillist - real/prolog - real/scs - spectral/expert - spectral/mate - spectral/para - spectral/treejoin Signed-off-by: Michal Terepeta Test Plan: build & run Reviewers: bgamari Reviewed By: bgamari Subscribers: snowleopard Differential Revision: https://phabricator.haskell.org/D3411 >--------------------------------------------------------------- c6b9143332b6171c251d2e72fb6a5484611031fb .gitignore | 2 +- real/anna/Main.hs | 2 +- real/anna/{ => runtime_files}/anna_table | 0 real/cacheprof/Main.hs | 4 ++-- real/cacheprof/{ => runtime_files}/cacheprof_hooks2_x86.s | 0 real/fluid/fluid.stdin | 2 +- real/fluid/{ => runtime_files}/chan8.dat | 0 real/hidden/Makefile | 2 +- real/hidden/{objects => runtime_files}/bookcase.plate | 0 real/hidden/{objects => runtime_files}/cube.plate | 0 real/hidden/{objects => runtime_files}/four.plate | 0 real/hidden/{objects => runtime_files}/horse.plate | 0 real/hidden/{objects => runtime_files}/houses.plate | 0 real/hidden/{objects => runtime_files}/pyramid.plate | 0 real/hidden/{objects => runtime_files}/rad.plate | 0 real/hidden/{objects => runtime_files}/table.plate | 0 real/maillist/maillist.stdin | 2 +- real/maillist/maillist.stdout | 2 +- real/maillist/{ => runtime_files}/addresses | 0 real/prolog/Main.hs | 2 +- real/prolog/prolog.stdout | 2 +- real/prolog/{ => runtime_files}/stdlib | 0 real/scs/Makefile | 2 +- real/scs/{ => runtime_files}/inverter.in | 0 spectral/expert/Main.hs | 2 +- spectral/expert/{ => runtime_files}/animals | 0 spectral/mate/Makefile | 6 +++++- spectral/mate/mate.stdout | 2 +- spectral/mate/{ => runtime_files}/ellerman.prob | 0 spectral/mate/{ => runtime_files}/ellerman.soln | 0 spectral/mate/{ => runtime_files}/fridlizius.prob | 0 spectral/mate/{ => runtime_files}/fridlizius.soln | 0 spectral/mate/{ => runtime_files}/heathcote3.prob | 0 spectral/mate/{ => runtime_files}/heathcote3.soln | 0 spectral/mate/{ => runtime_files}/holzhausen.prob | 0 spectral/mate/{ => runtime_files}/holzhausen.soln | 0 spectral/mate/{ => runtime_files}/kidson.prob | 0 spectral/mate/{ => runtime_files}/kohtz.prob | 0 spectral/mate/{ => runtime_files}/kohtz.soln | 0 spectral/mate/{ => runtime_files}/marin.prob | 0 spectral/mate/{ => runtime_files}/marin.soln | 0 spectral/mate/{ => runtime_files}/shinkman.prob | 0 spectral/mate/{ => runtime_files}/shinkman.soln | 0 spectral/mate/{ => runtime_files}/simple.prob | 0 spectral/mate/{ => runtime_files}/simple.soln | 0 spectral/mate/{ => runtime_files}/wurzburg.prob | 0 spectral/mate/{ => runtime_files}/wurzburg.soln | 0 spectral/para/Makefile | 2 +- spectral/para/{ => runtime_files}/input-data | 0 spectral/treejoin/Makefile | 2 +- spectral/treejoin/{ => runtime_files}/27000.1 | 0 spectral/treejoin/{ => runtime_files}/27000.2 | 0 52 files changed, 20 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 c6b9143332b6171c251d2e72fb6a5484611031fb From git at git.haskell.org Thu May 4 22:22:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 22:22:16 +0000 (UTC) Subject: [commit: packages/hpc] master: Add arcconfig (9c46599) Message-ID: <20170504222216.44D683A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : master Link : http://git.haskell.org/packages/hpc.git/commitdiff/9c46599cd370fa711de460994cfab492a5a1708d >--------------------------------------------------------------- commit 9c46599cd370fa711de460994cfab492a5a1708d Author: Ben Gamari Date: Thu May 4 15:15:07 2017 -0400 Add arcconfig >--------------------------------------------------------------- 9c46599cd370fa711de460994cfab492a5a1708d .arcconfig | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/.arcconfig b/.arcconfig new file mode 100644 index 0000000..b88cb34 --- /dev/null +++ b/.arcconfig @@ -0,0 +1,5 @@ +{ + "project.name" : "hpc", + "repository.callsign" : "HPC", + "phabricator.uri" : "https://phabricator.haskell.org" +} From git at git.haskell.org Thu May 4 22:22:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 22:22:18 +0000 (UTC) Subject: [commit: packages/hpc] master: Update HPC tests to include markup colors legend. (1544cf0) Message-ID: <20170504222218.490013A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : master Link : http://git.haskell.org/packages/hpc.git/commitdiff/1544cf04c38ab3b613dba1e0737de49c33321655 >--------------------------------------------------------------- commit 1544cf04c38ab3b613dba1e0737de49c33321655 Author: Santiago Munin Date: Thu May 4 15:15:56 2017 -0400 Update HPC tests to include markup colors legend. Summary: This should be reviewed together with https://phabricator.haskell.org/D3465 Reviewers: bgamari GHC Trac Issues: #11799 Differential Revision: https://phabricator.haskell.org/D3479 >--------------------------------------------------------------- 1544cf04c38ab3b613dba1e0737de49c33321655 tests/fork/hpc_fork.stdout | 3 +++ tests/function/tough.stdout | 3 +++ tests/function2/tough2.stdout | 3 +++ tests/simple/hpc001.stdout | 3 +++ tests/simple/tixs/hpc_markup_001.stdout | 3 +++ tests/simple/tixs/hpc_markup_002.stdout | 3 +++ 6 files changed, 18 insertions(+) diff --git a/tests/fork/hpc_fork.stdout b/tests/fork/hpc_fork.stdout index 26cd7e9..52f1f1b 100644 --- a/tests/fork/hpc_fork.stdout +++ b/tests/fork/hpc_fork.stdout @@ -39,6 +39,9 @@ span.spaces { background: white }
+never executed always true always false
+
+
     1 module Main where
     2 
     3 import System.Posix.Process
diff --git a/tests/function/tough.stdout b/tests/function/tough.stdout
index 21a31a0..0287052 100644
--- a/tests/function/tough.stdout
+++ b/tests/function/tough.stdout
@@ -49,6 +49,9 @@ span.spaces    { background: white }
 
 
 
+never executed always true always false
+
+
     1 import Control.Exception as E
     2 
     3 -- This test shows what hpc can really do.
diff --git a/tests/function2/tough2.stdout b/tests/function2/tough2.stdout
index 66bb3f8..dcfcd8d 100644
--- a/tests/function2/tough2.stdout
+++ b/tests/function2/tough2.stdout
@@ -49,6 +49,9 @@ span.spaces    { background: white }
 
 
 
+never executed always true always false
+
+
     1 \begin{code}
     2 import Control.Exception as E
     3 
diff --git a/tests/simple/hpc001.stdout b/tests/simple/hpc001.stdout
index 68190b1..03d524f 100644
--- a/tests/simple/hpc001.stdout
+++ b/tests/simple/hpc001.stdout
@@ -39,6 +39,9 @@ span.spaces    { background: white }
 
 
 
+never executed always true always false
+
+
     1 main = print (const "Hello" "World")
 
 
diff --git a/tests/simple/tixs/hpc_markup_001.stdout b/tests/simple/tixs/hpc_markup_001.stdout index 6f80922..d6e087a 100644 --- a/tests/simple/tixs/hpc_markup_001.stdout +++ b/tests/simple/tixs/hpc_markup_001.stdout @@ -14,6 +14,9 @@ span.spaces { background: white }
+never executed always true always false
+
+
     1 main = print (const "Hello" "World")
 
 
diff --git a/tests/simple/tixs/hpc_markup_002.stdout b/tests/simple/tixs/hpc_markup_002.stdout index ad7e017..38a790c 100644 --- a/tests/simple/tixs/hpc_markup_002.stdout +++ b/tests/simple/tixs/hpc_markup_002.stdout @@ -14,6 +14,9 @@ span.spaces { background: white }
+never executed always true always false
+
+
     1 -- entered oncemain = print (const "Hello" "World")
 
 
From git at git.haskell.org Thu May 4 22:22:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 22:22:41 +0000 (UTC) Subject: [commit: ghc] master: Bump nofib submodule (41a00fa) Message-ID: <20170504222241.684263A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/41a00fa1b9c3f82fc1919e3203488666f3fc75be/ghc >--------------------------------------------------------------- commit 41a00fa1b9c3f82fc1919e3203488666f3fc75be Author: Ben Gamari Date: Thu May 4 14:15:14 2017 -0400 Bump nofib submodule >--------------------------------------------------------------- 41a00fa1b9c3f82fc1919e3203488666f3fc75be nofib | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/nofib b/nofib index 7d7bc03..c6b9143 160000 --- a/nofib +++ b/nofib @@ -1 +1 @@ -Subproject commit 7d7bc03c385022c36c557be77c79c107633b4454 +Subproject commit c6b9143332b6171c251d2e72fb6a5484611031fb From git at git.haskell.org Thu May 4 22:22:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 22:22:38 +0000 (UTC) Subject: [commit: ghc] master: rts: Fix MachO from D3527 (8a60550) Message-ID: <20170504222238.ABB4F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8a6055048c0af75bbaed24df35a9b48afe1fa242/ghc >--------------------------------------------------------------- commit 8a6055048c0af75bbaed24df35a9b48afe1fa242 Author: Ben Gamari Date: Thu May 4 15:23:46 2017 -0400 rts: Fix MachO from D3527 We gave up on typedefing {Section,ObjectCode}FormatInfo structs but MachO never got the memo. >--------------------------------------------------------------- 8a6055048c0af75bbaed24df35a9b48afe1fa242 rts/linker/MachO.c | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/rts/linker/MachO.c b/rts/linker/MachO.c index 55ca853..f8b665a 100644 --- a/rts/linker/MachO.c +++ b/rts/linker/MachO.c @@ -99,9 +99,9 @@ bool ocMprotect_MachO( ObjectCode *oc ); void ocInit_MachO(ObjectCode * oc) { - oc->info = (ObjectCodeFormatInfo*)stgCallocBytes( - 1, sizeof(ObjectCodeFormatInfo), - "ocInit_MachO(ObjectCodeFormatInfo)"); + oc->info = (struct ObjectCodeFormatInfo*)stgCallocBytes( + 1, sizeof(struct ObjectCodeFormatInfo), + "ocInit_MachO(struct ObjectCodeFormatInfo)"); oc->info->header = (MachOHeader *) oc->image; oc->info->symCmd = NULL; oc->info->segCmd = NULL; From git at git.haskell.org Thu May 4 22:22:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 22:22:44 +0000 (UTC) Subject: [commit: ghc] master: Fix comment for compact region (4fcaf8e) Message-ID: <20170504222244.30E1E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4fcaf8e97db89b0c040ca33f0503faf3403b918f/ghc >--------------------------------------------------------------- commit 4fcaf8e97db89b0c040ca33f0503faf3403b918f Author: Takenobu Tani Date: Thu May 4 14:16:49 2017 -0400 Fix comment for compact region There were old module names: * Data.Compact -> GHC.Compact * Data.Compact.Internal -> GHC.Compact This commit is for ghc-8.2 branch. Test Plan: build Reviewers: austin, bgamari, hvr, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3522 >--------------------------------------------------------------- 4fcaf8e97db89b0c040ca33f0503faf3403b918f libraries/base/GHC/IO/Exception.hs | 2 +- libraries/ghc-compact/GHC/Compact.hs | 4 ++-- rts/sm/CNF.c | 4 ++-- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/libraries/base/GHC/IO/Exception.hs b/libraries/base/GHC/IO/Exception.hs index 17eda3d..9203f46 100644 --- a/libraries/base/GHC/IO/Exception.hs +++ b/libraries/base/GHC/IO/Exception.hs @@ -131,7 +131,7 @@ allocationLimitExceeded = toException AllocationLimitExceeded -- | Compaction found an object that cannot be compacted. Functions -- cannot be compacted, nor can mutable objects or pinned objects. --- See 'Data.Compact.compact'. +-- See 'GHC.Compact.compact'. -- -- @since 4.10.0.0 newtype CompactionFailed = CompactionFailed String diff --git a/libraries/ghc-compact/GHC/Compact.hs b/libraries/ghc-compact/GHC/Compact.hs index ea0663e..375e341 100644 --- a/libraries/ghc-compact/GHC/Compact.hs +++ b/libraries/ghc-compact/GHC/Compact.hs @@ -104,12 +104,12 @@ import GHC.Types -- -- The cost of compaction is similar to the cost of GC for the same -- data, but it is performed only once. However, because --- "Data.Compact.compact" does not stop-the-world, retaining internal +-- "GHC.Compact.compact" does not stop-the-world, retaining internal -- sharing during the compaction process is very costly. The user -- can choose whether to 'compact' or 'compactWithSharing'. -- -- When you have a @'Compact' a@, you can get a pointer to the actual object --- in the region using "Data.Compact.getCompact". The 'Compact' type +-- in the region using "GHC.Compact.getCompact". The 'Compact' type -- serves as handle on the region itself; you can use this handle -- to add data to a specific 'Compact' with 'compactAdd' or -- 'compactAddWithSharing' (giving you a new handle which corresponds diff --git a/rts/sm/CNF.c b/rts/sm/CNF.c index 72ab6f2..f740d05 100644 --- a/rts/sm/CNF.c +++ b/rts/sm/CNF.c @@ -4,7 +4,7 @@ * * GC support for immutable non-GCed structures, also known as Compact * Normal Forms (CNF for short). This provides the RTS support for - * the 'compact' package and the Data.Compact module. + * the 'compact' package and the GHC.Compact module. * * ---------------------------------------------------------------------------*/ @@ -51,7 +51,7 @@ Structure ~~~~~~~~~ - * In Data.Compact.Internal we have + * In GHC.Compact we have data Compact a = Compact Compact# a * The Compact# primitive object is operated on by the primitives. From git at git.haskell.org Thu May 4 22:22:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 22:22:46 +0000 (UTC) Subject: [commit: ghc] master: Add an Eq instance for UniqSet (a660844) Message-ID: <20170504222246.DE8763A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a660844c0859b7a2e76c15f2fb4abec209afea90/ghc >--------------------------------------------------------------- commit a660844c0859b7a2e76c15f2fb4abec209afea90 Author: David Feuer Date: Thu May 4 14:16:02 2017 -0400 Add an Eq instance for UniqSet I left that out by mistake, and it apparently breaks at least one existing plugin. Reviewers: christiaanb, austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3518 >--------------------------------------------------------------- a660844c0859b7a2e76c15f2fb4abec209afea90 compiler/utils/UniqFM.hs | 17 +++++++++++++++++ compiler/utils/UniqSet.hs | 6 ++++++ 2 files changed, 23 insertions(+) diff --git a/compiler/utils/UniqFM.hs b/compiler/utils/UniqFM.hs index 8214f17..71a092b 100644 --- a/compiler/utils/UniqFM.hs +++ b/compiler/utils/UniqFM.hs @@ -55,6 +55,7 @@ module UniqFM ( intersectUFM, intersectUFM_C, disjointUFM, + equalKeysUFM, nonDetFoldUFM, foldUFM, nonDetFoldUFM_Directly, anyUFM, allUFM, seqEltsUFM, mapUFM, mapUFM_Directly, @@ -76,6 +77,11 @@ import Outputable import Data.List (foldl') import qualified Data.IntMap as M +#if MIN_VERSION_containers(0,5,9) +import qualified Data.IntMap.Merge.Lazy as M +import Control.Applicative (Const (..)) +import qualified Data.Monoid as Mon +#endif import qualified Data.IntSet as S import Data.Typeable import Data.Data @@ -339,6 +345,17 @@ nonDetUFMToList (UFM m) = map (\(k, v) -> (getUnique k, v)) $ M.toList m ufmToIntMap :: UniqFM elt -> M.IntMap elt ufmToIntMap (UFM m) = m +-- Determines whether two 'UniqFm's contain the same keys. +equalKeysUFM :: UniqFM a -> UniqFM b -> Bool +#if MIN_VERSION_containers(0,5,9) +equalKeysUFM (UFM m1) (UFM m2) = Mon.getAll $ getConst $ + M.mergeA (M.traverseMissing (\_ _ -> Const (Mon.All False))) + (M.traverseMissing (\_ _ -> Const (Mon.All False))) + (M.zipWithAMatched (\_ _ _ -> Const (Mon.All True))) m1 m2 +#else +equalKeysUFM (UFM m1) (UFM m2) = M.keys m1 == M.keys m2 +#endif + -- Instances #if __GLASGOW_HASKELL__ > 710 diff --git a/compiler/utils/UniqSet.hs b/compiler/utils/UniqSet.hs index ede900a..d9d51f4 100644 --- a/compiler/utils/UniqSet.hs +++ b/compiler/utils/UniqSet.hs @@ -128,6 +128,12 @@ mapUniqSet :: Uniquable b => (a -> b) -> UniqSet a -> UniqSet b -- the invariant. newtype UniqSet a = UniqSet {getUniqSet' :: UniqFM a} deriving Data + +-- Two 'UniqSet's are considered equal if they contain the same +-- uniques. +instance Eq (UniqSet a) where + UniqSet a == UniqSet b = equalKeysUFM a b + getUniqSet :: UniqSet a -> UniqFM a getUniqSet = getUniqSet' From git at git.haskell.org Thu May 4 22:22:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 22:22:49 +0000 (UTC) Subject: [commit: ghc] master: user-guide: fix links to compact region (0b41bbc) Message-ID: <20170504222249.A33FD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0b41bbcdef5f690e6a8f549787775a52e6b70c5b/ghc >--------------------------------------------------------------- commit 0b41bbcdef5f690e6a8f549787775a52e6b70c5b Author: Takenobu Tani Date: Thu May 4 14:16:32 2017 -0400 user-guide: fix links to compact region There were broken links in users_guide for compact region. * Data-Compact -> GHC-Compact * compact- at LIBRARY_compact_VERSION@ -> ghc-compact- at LIBRARY_compact_VERSION@ This commit is for ghc-8.2 branch. Test Plan: build Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3521 >--------------------------------------------------------------- 0b41bbcdef5f690e6a8f549787775a52e6b70c5b docs/users_guide/8.2.1-notes.rst | 4 ++-- docs/users_guide/ghc_config.py.in | 2 +- docs/users_guide/sooner.rst | 2 +- 3 files changed, 4 insertions(+), 4 deletions(-) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index 3b1a1f1..57c22a3 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -281,8 +281,8 @@ Runtime system move long-lived data outside of the heap so that the garbage collector does not have to trace it repeatedly. Compacted data can also be serialized, stored, and deserialized again later by the same - program. For more details see the :compact-ref:`Data.Compact - ` module. + program. For more details see the :compact-ref:`GHC.Compact + ` module. - There is new support for improving performance on machines with a Non-Uniform Memory Architecture (NUMA). See :rts-flag:`--numa`. diff --git a/docs/users_guide/ghc_config.py.in b/docs/users_guide/ghc_config.py.in index e2783e4..6711c6b 100644 --- a/docs/users_guide/ghc_config.py.in +++ b/docs/users_guide/ghc_config.py.in @@ -1,7 +1,7 @@ extlinks = { 'base-ref': ('../libraries/base- at LIBRARY_base_VERSION@/%s', ''), 'cabal-ref': ('../libraries/Cabal- at LIBRARY_Cabal_VERSION@/%s', ''), - 'compact-ref': ('../libraries/compact- at LIBRARY_compact_VERSION@/%s', ''), + 'compact-ref': ('../libraries/ghc-compact- at LIBRARY_compact_VERSION@/%s', ''), 'ghc-prim-ref': ('../libraries/ghc-prim- at LIBRARY_ghc_prim_VERSION@/%s', ''), 'ghc-ticket': ('http://ghc.haskell.org/trac/ghc/ticket/%s', 'Trac #'), 'ghc-wiki': ('http://ghc.haskell.org/trac/ghc/wiki/%s', 'Trac #'), diff --git a/docs/users_guide/sooner.rst b/docs/users_guide/sooner.rst index 702648f..48958d6 100644 --- a/docs/users_guide/sooner.rst +++ b/docs/users_guide/sooner.rst @@ -312,7 +312,7 @@ Use a bigger heap! calculate a value based on the amount of live data. Compact your data: - The :compact-ref:`Data.Compact ` module + The :compact-ref:`GHC.Compact ` module provides a way to make garbage collection more efficient for long-lived data structures. Compacting a data structure collects the objects together in memory, where they are treated as a single From git at git.haskell.org Thu May 4 22:22:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 22:22:52 +0000 (UTC) Subject: [commit: ghc] master: Pass -ffrontend-opt arguments to frontend plugin in the correct order (db10b79) Message-ID: <20170504222252.688443A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/db10b79994f7728cbaaa906c6f6eda0b6783df29/ghc >--------------------------------------------------------------- commit db10b79994f7728cbaaa906c6f6eda0b6783df29 Author: doug Date: Thu May 4 14:16:17 2017 -0400 Pass -ffrontend-opt arguments to frontend plugin in the correct order Previously they were passed in the reverse order that they're specified on the command line. Add a haddock to frontendPluginOpts in DynFlags.hs. Modify test frontend01 to cover the case of multiple -ffrontend-opt. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13632 Differential Revision: https://phabricator.haskell.org/D3520 >--------------------------------------------------------------- db10b79994f7728cbaaa906c6f6eda0b6783df29 compiler/main/DynFlags.hs | 2 ++ ghc/Main.hs | 3 ++- testsuite/tests/plugins/Makefile | 2 +- testsuite/tests/plugins/frontend01.stdout | 2 +- 4 files changed, 6 insertions(+), 3 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 383a71a..5771fd6 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -796,6 +796,8 @@ data DynFlags = DynFlags { pluginModNames :: [ModuleName], pluginModNameOpts :: [(ModuleName,String)], frontendPluginOpts :: [String], + -- ^ the @-ffrontend-opt@ flags given on the command line, in *reverse* + -- order that they're specified on the command line. -- GHC API hooks hooks :: Hooks, diff --git a/ghc/Main.hs b/ghc/Main.hs index 6ece430..0a4e17a 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -837,7 +837,8 @@ doFrontend modname _ = pluginError [modname] doFrontend modname srcs = do hsc_env <- getSession frontend_plugin <- liftIO $ loadFrontendPlugin hsc_env modname - frontend frontend_plugin (frontendPluginOpts (hsc_dflags hsc_env)) srcs + frontend frontend_plugin + (reverse $ frontendPluginOpts (hsc_dflags hsc_env)) srcs #endif -- ----------------------------------------------------------------------------- diff --git a/testsuite/tests/plugins/Makefile b/testsuite/tests/plugins/Makefile index 46fdc7d..efe17ef 100644 --- a/testsuite/tests/plugins/Makefile +++ b/testsuite/tests/plugins/Makefile @@ -34,7 +34,7 @@ T10294a: frontend01: $(RM) FrontendPlugin.hi FrontendPlugin.o frontend01 frontend01.hi frontend.o "$(TEST_HC)" $(TEST_HC_OPTS) $(ghcPluginWayFlags) -Wall -package ghc -c FrontendPlugin.hs - "$(TEST_HC)" $(TEST_HC_OPTS) $(ghcPluginWayFlags) --frontend FrontendPlugin -ffrontend-opt foobar frontend01 + "$(TEST_HC)" $(TEST_HC_OPTS) $(ghcPluginWayFlags) --frontend FrontendPlugin -ffrontend-opt foo -ffrontend-opt bar frontend01 ./frontend01 # -hide-all-plugin-packages + -package (this should not work!) diff --git a/testsuite/tests/plugins/frontend01.stdout b/testsuite/tests/plugins/frontend01.stdout index 84950bc..234c91c 100644 --- a/testsuite/tests/plugins/frontend01.stdout +++ b/testsuite/tests/plugins/frontend01.stdout @@ -1,4 +1,4 @@ -["foobar"] +["foo","bar"] [1 of 1] Compiling Main ( frontend01.hs, frontend01.o ) Linking frontend01 ... hello world From git at git.haskell.org Thu May 4 22:22:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 22:22:55 +0000 (UTC) Subject: [commit: ghc] master: Fix markdown for new GitHub Flavored Markdown (74f3153) Message-ID: <20170504222255.1E5DA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/74f31539ce48a218922368ca62e1c3c6023f27a8/ghc >--------------------------------------------------------------- commit 74f31539ce48a218922368ca62e1c3c6023f27a8 Author: Takenobu Tani Date: Thu May 4 14:19:37 2017 -0400 Fix markdown for new GitHub Flavored Markdown Delete whitespace between brackets. Because Github Flavored Markdown was changed [1]. [1]: https://githubengineering.com/a-formal-spec-for-github-markdown/ Test Plan: build Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3534 >--------------------------------------------------------------- 74f31539ce48a218922368ca62e1c3c6023f27a8 README.md | 22 +++++++++++----------- 1 file changed, 11 insertions(+), 11 deletions(-) diff --git a/README.md b/README.md index 59f83bf..02bf4a8 100644 --- a/README.md +++ b/README.md @@ -29,7 +29,7 @@ There are two ways to get a source tree: $ git clone --recursive git://git.haskell.org/ghc.git Note: cloning GHC from Github requires a special setup. See [Getting a GHC - repository from Github] [7]. + repository from Github][7]. *See the GHC team's working conventions regarding [how to contribute a patch to GHC](http://ghc.haskell.org/trac/ghc/wiki/WorkingConventions/FixingBugs).* First time contributors are encouraged to get started by just sending a Pull Request. @@ -37,19 +37,19 @@ There are two ways to get a source tree: Building & Installing ===================== -For full information on building GHC, see the [GHC Building Guide] [3]. +For full information on building GHC, see the [GHC Building Guide][3]. Here follows a summary - if you get into trouble, the Building Guide has all the answers. Before building GHC you may need to install some other tools and -libraries. See, [Setting up your system for building GHC] [8]. +libraries. See, [Setting up your system for building GHC][8]. -*NB.* In particular, you need [GHC] [1] installed in order to build GHC, +*NB.* In particular, you need [GHC][1] installed in order to build GHC, because the compiler is itself written in Haskell. You also need -[Happy] [4], [Alex] [5], and [Cabal] [9]. For instructions on how -to port GHC to a new platform, see the [GHC Building Guide] [3]. +[Happy][4], [Alex][5], and [Cabal][9]. For instructions on how +to port GHC to a new platform, see the [GHC Building Guide][3]. -For building library documentation, you'll need [Haddock] [6]. To build +For building library documentation, you'll need [Haddock][6]. To build the compiler documentation, you need [Sphinx](http://www.sphinx-doc.org/) and Xelatex (only for PDF output). @@ -71,7 +71,7 @@ almost always a win regardless of how many cores you have. As a simple rule, you should have about N+1 jobs, where `N` is the amount of cores you have.) The `./boot` step is only necessary if this is a tree checked out -from git. For source distributions downloaded from [GHC's web site] [1], +from git. For source distributions downloaded from [GHC's web site][1], this step has already been performed. These steps give you the default build, which includes everything @@ -83,12 +83,12 @@ Filing bugs and feature requests If you've encountered what you believe is a bug in GHC, or you'd like to propose a feature request, please let us know! Submit a ticket in -our [bug tracker] [10] and we'll be sure to look into it. Remember: +our [bug tracker][10] and we'll be sure to look into it. Remember: **Filing a bug is the best way to make sure your issue isn't lost over time**, so please feel free. If you're an active user of GHC, you may also be interested in joining -the [glasgow-haskell-users] [11] mailing list, where developers and +the [glasgow-haskell-users][11] mailing list, where developers and GHC users discuss various topics and hang out. Hacking & Developing GHC @@ -103,7 +103,7 @@ Contributors & Acknowledgements =============================== GHC in its current form wouldn't exist without the hard work of -[its many contributors] [12]. Over time, it has grown to include the +[its many contributors][12]. Over time, it has grown to include the efforts and research of many institutions, highly talented people, and groups from around the world. We'd like to thank them all, and invite you to join! From git at git.haskell.org Thu May 4 22:22:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 22:22:58 +0000 (UTC) Subject: [commit: ghc] master: Implement sequential name lookup properly (1829d26) Message-ID: <20170504222258.324713A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1829d265662ca8d052df3e5df1aa1137b19e39ce/ghc >--------------------------------------------------------------- commit 1829d265662ca8d052df3e5df1aa1137b19e39ce Author: Matthew Pickering Date: Thu May 4 14:15:43 2017 -0400 Implement sequential name lookup properly Previously we would run all the monadic actions and then combine their results. This caused problems if later actions raised errors but earlier lookups suceeded. We only want to run later lookups if the earlier ones fail. Fixes #13622 Reviewers: RyanGlScott, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #13622 Differential Revision: https://phabricator.haskell.org/D3515 >--------------------------------------------------------------- 1829d265662ca8d052df3e5df1aa1137b19e39ce compiler/typecheck/TcRnExports.hs | 26 +++++++++++++++++++------- testsuite/tests/module/T13622.hs | 5 +++++ testsuite/tests/module/all.T | 1 + 3 files changed, 25 insertions(+), 7 deletions(-) diff --git a/compiler/typecheck/TcRnExports.hs b/compiler/typecheck/TcRnExports.hs index 2da1862..1389e74 100644 --- a/compiler/typecheck/TcRnExports.hs +++ b/compiler/typecheck/TcRnExports.hs @@ -445,7 +445,7 @@ lookupChildrenExport parent rdr_items = let bareName = unLoc n lkup v = lookupExportChild parent (setRdrNameSpace bareName v) - name <- fmap mconcat . mapM lkup $ + name <- tryChildLookupResult $ map lkup $ (choosePossibleNamespaces (rdrNameSpace bareName)) -- Default to data constructors for slightly better error @@ -461,6 +461,17 @@ lookupChildrenExport parent rdr_items = FoundName name -> return $ Left (L (getLoc n) name) NameErr err_msg -> reportError err_msg >> failM +tryChildLookupResult :: [RnM ChildLookupResult] -> RnM ChildLookupResult +tryChildLookupResult [x] = x +tryChildLookupResult (x:xs) = do + res <- x + case res of + FoundFL {} -> return res + FoundName {} -> return res + NameErr {} -> return res + _ -> tryChildLookupResult xs +tryChildLookupResult _ = panic "tryChildLookupResult:empty list" + -- | Also captures the current context @@ -580,19 +591,20 @@ data DisambigInfo instance Monoid DisambigInfo where mempty = NoOccurrence -- This is the key line: We prefer disambiguated occurrences to other - -- names. - UniqueOccurrence _ `mappend` DisambiguatedOccurrence g' = DisambiguatedOccurrence g' - DisambiguatedOccurrence g' `mappend` UniqueOccurrence _ = DisambiguatedOccurrence g' + -- names. Notice that two disambiguated occurences are not ambiguous as + -- there is an internal invariant that a list of `DisambigInfo` arises + -- from a list of GREs which all have the same OccName. Thus, if we ever + -- have two DisambiguatedOccurences then they must have arisen from the + -- same GRE and hence it's safe to discard one. + _ `mappend` DisambiguatedOccurrence g' = DisambiguatedOccurrence g' + DisambiguatedOccurrence g' `mappend` _ = DisambiguatedOccurrence g' NoOccurrence `mappend` m = m m `mappend` NoOccurrence = m UniqueOccurrence g `mappend` UniqueOccurrence g' = AmbiguousOccurrence [g, g'] UniqueOccurrence g `mappend` AmbiguousOccurrence gs = AmbiguousOccurrence (g:gs) - DisambiguatedOccurrence g `mappend` DisambiguatedOccurrence g' = AmbiguousOccurrence [g, g'] - DisambiguatedOccurrence g `mappend` AmbiguousOccurrence gs = AmbiguousOccurrence (g:gs) AmbiguousOccurrence gs `mappend` UniqueOccurrence g' = AmbiguousOccurrence (g':gs) - AmbiguousOccurrence gs `mappend` DisambiguatedOccurrence g' = AmbiguousOccurrence (g':gs) AmbiguousOccurrence gs `mappend` AmbiguousOccurrence gs' = AmbiguousOccurrence (gs ++ gs') diff --git a/testsuite/tests/module/T13622.hs b/testsuite/tests/module/T13622.hs new file mode 100644 index 0000000..037283e --- /dev/null +++ b/testsuite/tests/module/T13622.hs @@ -0,0 +1,5 @@ +module Bug (Bits(Bits)) where + +import qualified Data.Bits as Bits + +newtype Bits = Bits Int diff --git a/testsuite/tests/module/all.T b/testsuite/tests/module/all.T index 6d05c77..5404f19 100644 --- a/testsuite/tests/module/all.T +++ b/testsuite/tests/module/all.T @@ -283,4 +283,5 @@ test('T11970A', [], multimod_compile, ['T11970A','-Wunused-imports']) test('T11970B', normal, compile_fail, ['']) test('MultiExport', normal, compile, ['']) test('T13528', normal, compile, ['']) +test('T13622', normal, compile, ['']) From git at git.haskell.org Thu May 4 22:23:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 22:23:01 +0000 (UTC) Subject: [commit: ghc] master: Add regression test for #11616 (03ca391) Message-ID: <20170504222301.6DD763A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/03ca391f14f97486fd1c66d9c9d99686ae25cc10/ghc >--------------------------------------------------------------- commit 03ca391f14f97486fd1c66d9c9d99686ae25cc10 Author: Ryan Scott Date: Thu May 4 14:19:26 2017 -0400 Add regression test for #11616 The code in #11616 has been working for a while (ever since 8.0.1), so let's add a regression test for it to put the nail in the coffin. Test Plan: make test TEST=T11616 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #11616 Differential Revision: https://phabricator.haskell.org/D3531 >--------------------------------------------------------------- 03ca391f14f97486fd1c66d9c9d99686ae25cc10 testsuite/tests/polykinds/T11616.hs | 19 +++++++++++++++++++ testsuite/tests/polykinds/all.T | 1 + 2 files changed, 20 insertions(+) diff --git a/testsuite/tests/polykinds/T11616.hs b/testsuite/tests/polykinds/T11616.hs new file mode 100644 index 0000000..378032b --- /dev/null +++ b/testsuite/tests/polykinds/T11616.hs @@ -0,0 +1,19 @@ +{-# LANGUAGE AllowAmbiguousTypes #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE TypeInType #-} +module T11616 where + +class Whoami a where + whoami :: String + +instance Whoami Int where + whoami = "int" + +instance Whoami Bool where + whoami = "[y/n]" + +instance Whoami Maybe where + whoami = "call me maybe" + +whoisint :: String +whoisint = whoami @Int diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index e534e08..b59cbe6 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -140,6 +140,7 @@ test('T11362', normal, compile, ['-dunique-increment=-1']) # -dunique-increment=-1 doesn't work inside the file test('T11399', normal, compile_fail, ['']) test('T11611', normal, compile_fail, ['']) +test('T11616', normal, compile, ['']) test('T11648', normal, compile, ['']) test('T11648b', normal, compile_fail, ['']) test('KindVType', normal, compile_fail, ['']) From git at git.haskell.org Thu May 4 22:23:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 22:23:04 +0000 (UTC) Subject: [commit: ghc] master: hpc: Output a legend at the top of output files (8a2c247) Message-ID: <20170504222304.314AD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8a2c2476b300969514888cb2084d083f8d18b6b0/ghc >--------------------------------------------------------------- commit 8a2c2476b300969514888cb2084d083f8d18b6b0 Author: Santiago Munin Date: Thu May 4 15:10:54 2017 -0400 hpc: Output a legend at the top of output files Updates hpc submodule. Reviewers: austin, bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #11799 Differential Revision: https://phabricator.haskell.org/D3465 >--------------------------------------------------------------- 8a2c2476b300969514888cb2084d083f8d18b6b0 libraries/hpc | 2 +- utils/hpc/HpcMarkup.hs | 7 +++++++ 2 files changed, 8 insertions(+), 1 deletion(-) diff --git a/libraries/hpc b/libraries/hpc index b28546c..1544cf0 160000 --- a/libraries/hpc +++ b/libraries/hpc @@ -1 +1 @@ -Subproject commit b28546ca003c6dbff586609a093e8c8091c34b14 +Subproject commit 1544cf04c38ab3b613dba1e0737de49c33321655 diff --git a/utils/hpc/HpcMarkup.hs b/utils/hpc/HpcMarkup.hs index fb68eac..ca30471 100644 --- a/utils/hpc/HpcMarkup.hs +++ b/utils/hpc/HpcMarkup.hs @@ -250,6 +250,13 @@ genHtmlFromMod dest_dir flags tix theFunTotals invertOutput = do "", "", "", + "
",
+                     concat [
+                         "",
+                         "never executed ",
+                         "always true ",
+                         "always false"],
+                     "
", "
"] ++ addLines content' ++ "\n
\n\n\n"; From git at git.haskell.org Thu May 4 22:23:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 22:23:06 +0000 (UTC) Subject: [commit: ghc] master: CoreTidy: Don't seq unfoldings (b3da6a6) Message-ID: <20170504222306.E257B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b3da6a6c3546562d5c5e83b8af5d3fd04c07e0c1/ghc >--------------------------------------------------------------- commit b3da6a6c3546562d5c5e83b8af5d3fd04c07e0c1 Author: Ben Gamari Date: Tue May 2 11:36:47 2017 -0400 CoreTidy: Don't seq unfoldings Previously we would force uf_is_value and friends to ensure that we didn't retain a reference to the pre-tidying template, resulting in a space leak. Instead, we now just reinitialize these fields (despite the fact that they should not have changed). This may result in a bit more computation, but most of the time we won't ever evaluate them anyways, so the damage shouldn't be so bad. See #13564. >--------------------------------------------------------------- b3da6a6c3546562d5c5e83b8af5d3fd04c07e0c1 compiler/coreSyn/CoreTidy.hs | 18 +++++++++++------- 1 file changed, 11 insertions(+), 7 deletions(-) diff --git a/compiler/coreSyn/CoreTidy.hs b/compiler/coreSyn/CoreTidy.hs index 89ce692..3578b0b 100644 --- a/compiler/coreSyn/CoreTidy.hs +++ b/compiler/coreSyn/CoreTidy.hs @@ -15,7 +15,7 @@ module CoreTidy ( #include "HsVersions.h" import CoreSyn -import CoreSeq ( seqUnfolding ) +import CoreUnfold ( mkCoreUnfolding ) import CoreArity import Id import IdInfo @@ -221,17 +221,21 @@ tidyUnfolding tidy_env df@(DFunUnfolding { df_bndrs = bndrs, df_args = args }) _ (tidy_env', bndrs') = tidyBndrs tidy_env bndrs tidyUnfolding tidy_env - unf@(CoreUnfolding { uf_tmpl = unf_rhs, uf_src = src }) + (CoreUnfolding { uf_tmpl = unf_rhs, uf_is_top = top_lvl + , uf_src = src, uf_guidance = guidance }) unf_from_rhs | isStableSource src - = seqIt $ unf { uf_tmpl = tidyExpr tidy_env unf_rhs } -- Preserves OccInfo - -- This seqIt avoids a space leak: otherwise the uf_is_value, - -- uf_is_conlike, ... fields may retain a reference to the - -- pre-tidied expression forever (ToIface doesn't look at them) + = mkCoreUnfolding src top_lvl (tidyExpr tidy_env unf_rhs) guidance + -- Preserves OccInfo + + -- Note that uf_is_value and friends may be a thunk containing a reference + -- to the old template. Consequently it is important that we rebuild them, + -- despite the fact that they won't change, to avoid a space leak (since, + -- e.g., ToIface doesn't look at them; see #13564). This is the same + -- approach we use in Simplify.simplUnfolding and TcIface.tcUnfolding. | otherwise = unf_from_rhs - where seqIt unf = seqUnfolding unf `seq` unf tidyUnfolding _ unf _ = unf -- NoUnfolding or OtherCon {- From git at git.haskell.org Thu May 4 22:23:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 May 2017 22:23:09 +0000 (UTC) Subject: [commit: ghc] master: TcTypeable: Simplify (c8e4d4b) Message-ID: <20170504222309.A84C73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c8e4d4b387d6d057dea98d6a595e3712f24289dc/ghc >--------------------------------------------------------------- commit c8e4d4b387d6d057dea98d6a595e3712f24289dc Author: Ben Gamari Date: Thu May 4 10:06:33 2017 -0400 TcTypeable: Simplify Simon pointed out that the zonk of the tyConKinds was redundant as tycon kinds will never contain mutable variables. This allows us to remove tycon_kind. Add a few commments clarifying the need to bring TyCon binders into scope before typechecking bindings. >--------------------------------------------------------------- c8e4d4b387d6d057dea98d6a595e3712f24289dc compiler/typecheck/TcTypeable.hs | 59 +++++++++++++++++++--------------------- 1 file changed, 28 insertions(+), 31 deletions(-) diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index 4c6076e..5b633ff 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -16,7 +16,6 @@ import TyCoRep( Type(..), TyLit(..) ) import TcEnv import TcEvidence ( mkWpTyApps ) import TcRnMonad -import TcMType ( zonkTcType ) import HscTypes ( lookupId ) import PrelNames import TysPrim ( primTyCons ) @@ -209,11 +208,12 @@ mkModIdRHS mod * * ********************************************************************* -} --- | Information we need about a 'TyCon' to generate its representation. +-- | Information we need about a 'TyCon' to generate its representation. We +-- carry the 'Id' in order to share it between the generation of the @TyCon@ and +-- @KindRep@ bindings. data TypeableTyCon = TypeableTyCon { tycon :: !TyCon - , tycon_kind :: !Kind , tycon_rep_id :: !Id } @@ -224,7 +224,7 @@ data TypeRepTodo , pkg_fingerprint :: !Fingerprint -- ^ Package name fingerprint , mod_fingerprint :: !Fingerprint -- ^ Module name fingerprint , todo_tycons :: [TypeableTyCon] - -- ^ The 'TyCon's in need of bindings and their zonked kinds + -- ^ The 'TyCon's in need of bindings kinds } | ExportedKindRepsTodo [(Kind, Id)] -- ^ Build exported 'KindRep' bindings for the given set of kinds. @@ -232,30 +232,25 @@ data TypeRepTodo todoForTyCons :: Module -> Id -> [TyCon] -> TcM TypeRepTodo todoForTyCons mod mod_id tycons = do trTyConTy <- mkTyConTy <$> tcLookupTyCon trTyConTyConName - let mkRepId :: TyConRepName -> Id - mkRepId rep_name = mkExportedVanillaId rep_name trTyConTy - - tycons <- sequence - [ do kind <- zonkTcType $ tyConKind tc'' - return TypeableTyCon { tycon = tc'' - , tycon_kind = kind - , tycon_rep_id = mkRepId rep_name - } - | tc <- tycons - , tc' <- tc : tyConATs tc - -- If the tycon itself isn't typeable then we needn't look - -- at its promoted datacons as their kinds aren't Typeable - , Just _ <- pure $ tyConRepName_maybe tc' - -- We need type representations for any associated types - , let promoted = map promoteDataCon (tyConDataCons tc') - , tc'' <- tc' : promoted - , Just rep_name <- pure $ tyConRepName_maybe tc'' - ] - let typeable_tycons = filter is_typeable tycons - is_typeable (TypeableTyCon {..}) = - --pprTrace "todoForTycons" (ppr tycon $$ ppr bare_kind $$ ppr is_typeable) - (typeIsTypeable bare_kind) - where bare_kind = dropForAlls tycon_kind + let mk_rep_id :: TyConRepName -> Id + mk_rep_id rep_name = mkExportedVanillaId rep_name trTyConTy + + let typeable_tycons :: [TypeableTyCon] + typeable_tycons = + [ TypeableTyCon { tycon = tc'' + , tycon_rep_id = mk_rep_id rep_name + } + | tc <- tycons + , tc' <- tc : tyConATs tc + -- If the tycon itself isn't typeable then we needn't look + -- at its promoted datacons as their kinds aren't Typeable + , Just _ <- pure $ tyConRepName_maybe tc' + -- We need type representations for any associated types + , let promoted = map promoteDataCon (tyConDataCons tc') + , tc'' <- tc' : promoted + , Just rep_name <- pure $ tyConRepName_maybe tc'' + , typeIsTypeable $ dropForAlls $ tyConKind tc'' + ] return TypeRepTodo { mod_rep_expr = nlHsVar mod_id , pkg_fingerprint = pkg_fpr , mod_fingerprint = mod_fpr @@ -279,7 +274,9 @@ mkTypeRepTodoBinds todos -- First extend the type environment with all of the bindings -- which we are going to produce since we may need to refer to them - -- while generating the kind representations of other types. + -- while generating kind representations (namely, when we want to + -- represent a TyConApp in a kind, we must be able to look up the + -- TyCon associated with the applied type constructor). ; let produced_bndrs :: [Id] produced_bndrs = [ tycon_rep_id | todo@(TypeRepTodo{}) <- todos @@ -402,9 +399,9 @@ mkTyConRepBinds :: TypeableStuff -> TypeRepTodo -> TypeableTyCon -> KindRepM (LHsBinds Id) mkTyConRepBinds stuff@(Stuff {..}) todo (TypeableTyCon {..}) = do -- Make a KindRep - let (bndrs, kind) = splitForAllTyVarBndrs tycon_kind + let (bndrs, kind) = splitForAllTyVarBndrs (tyConKind tycon) liftTc $ traceTc "mkTyConKindRepBinds" - (ppr tycon $$ ppr tycon_kind $$ ppr kind) + (ppr tycon $$ ppr (tyConKind tycon) $$ ppr kind) let ctx = mkDeBruijnContext (map binderVar bndrs) kind_rep <- getKindRep stuff ctx kind From git at git.haskell.org Fri May 5 02:54:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 May 2017 02:54:36 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Deal with exceptions in dsWhenNoErrs (c7642de) Message-ID: <20170505025436.E7CCD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/c7642debda55509d805036c28c9804f6c587d44b/ghc >--------------------------------------------------------------- commit c7642debda55509d805036c28c9804f6c587d44b Author: Simon Peyton Jones Date: Thu May 4 13:33:04 2017 +0100 Deal with exceptions in dsWhenNoErrs Gracious me. Ever since this patch commit 374457809de343f409fbeea0a885877947a133a2 Author: Jan Stolarek Date: Fri Jul 11 13:54:45 2014 +0200 Injective type families TcRnMonad.askNoErrs has been wrong. It looked like this askNoErrs :: TcRn a -> TcRn (a, Bool) askNoErrs m = do { errs_var <- newTcRef emptyMessages ; res <- setErrsVar errs_var m ; (warns, errs) <- readTcRef errs_var ; addMessages (warns, errs) ; return (res, isEmptyBag errs) } The trouble comes if 'm' throws an exception in the TcRn monad. Then 'errs_var is never read, so any errors are simply lost. This mistake was then propgated into DsMonad.dsWhenNoErrs, where it gave rise to Trac #13642. Thank to Ryan for narrowing it down so sharply. I did some refactoring, as usual. (cherry picked from commit e77019767fe5327011c6dc8fe089c64884120aab) >--------------------------------------------------------------- c7642debda55509d805036c28c9804f6c587d44b compiler/deSugar/DsMonad.hs | 32 +++++++++--- compiler/ghci/RtClosureInspect.hs | 10 ++-- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcRnMonad.hs | 102 +++++++++++++++++++------------------- compiler/typecheck/TcSplice.hs | 8 +-- testsuite/tests/th/T13642.hs | 9 ++++ testsuite/tests/th/T13642.stderr | 4 ++ testsuite/tests/th/all.T | 1 + 8 files changed, 94 insertions(+), 74 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 c7642debda55509d805036c28c9804f6c587d44b From git at git.haskell.org Fri May 5 02:54:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 May 2017 02:54:43 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: user-guide: fix links to compact region (a200ff6) Message-ID: <20170505025443.177273A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/a200ff64eda6a3c4f58c52be4e7f22bfb8b5393c/ghc >--------------------------------------------------------------- commit a200ff64eda6a3c4f58c52be4e7f22bfb8b5393c Author: Takenobu Tani Date: Thu May 4 14:16:32 2017 -0400 user-guide: fix links to compact region There were broken links in users_guide for compact region. * Data-Compact -> GHC-Compact * compact- at LIBRARY_compact_VERSION@ -> ghc-compact- at LIBRARY_compact_VERSION@ This commit is for ghc-8.2 branch. Test Plan: build Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3521 (cherry picked from commit 0b41bbcdef5f690e6a8f549787775a52e6b70c5b) >--------------------------------------------------------------- a200ff64eda6a3c4f58c52be4e7f22bfb8b5393c docs/users_guide/8.2.1-notes.rst | 4 ++-- docs/users_guide/ghc_config.py.in | 2 +- docs/users_guide/sooner.rst | 2 +- 3 files changed, 4 insertions(+), 4 deletions(-) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index d4b7045..3cf3833 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -281,8 +281,8 @@ Runtime system move long-lived data outside of the heap so that the garbage collector does not have to trace it repeatedly. Compacted data can also be serialized, stored, and deserialized again later by the same - program. For more details see the :compact-ref:`Data.Compact - ` module. + program. For more details see the :compact-ref:`GHC.Compact + ` module. - There is new support for improving performance on machines with a Non-Uniform Memory Architecture (NUMA). See :rts-flag:`--numa`. diff --git a/docs/users_guide/ghc_config.py.in b/docs/users_guide/ghc_config.py.in index e2783e4..6711c6b 100644 --- a/docs/users_guide/ghc_config.py.in +++ b/docs/users_guide/ghc_config.py.in @@ -1,7 +1,7 @@ extlinks = { 'base-ref': ('../libraries/base- at LIBRARY_base_VERSION@/%s', ''), 'cabal-ref': ('../libraries/Cabal- at LIBRARY_Cabal_VERSION@/%s', ''), - 'compact-ref': ('../libraries/compact- at LIBRARY_compact_VERSION@/%s', ''), + 'compact-ref': ('../libraries/ghc-compact- at LIBRARY_compact_VERSION@/%s', ''), 'ghc-prim-ref': ('../libraries/ghc-prim- at LIBRARY_ghc_prim_VERSION@/%s', ''), 'ghc-ticket': ('http://ghc.haskell.org/trac/ghc/ticket/%s', 'Trac #'), 'ghc-wiki': ('http://ghc.haskell.org/trac/ghc/wiki/%s', 'Trac #'), diff --git a/docs/users_guide/sooner.rst b/docs/users_guide/sooner.rst index 702648f..48958d6 100644 --- a/docs/users_guide/sooner.rst +++ b/docs/users_guide/sooner.rst @@ -312,7 +312,7 @@ Use a bigger heap! calculate a value based on the amount of live data. Compact your data: - The :compact-ref:`Data.Compact ` module + The :compact-ref:`GHC.Compact ` module provides a way to make garbage collection more efficient for long-lived data structures. Compacting a data structure collects the objects together in memory, where they are treated as a single From git at git.haskell.org Fri May 5 02:54:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 May 2017 02:54:40 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Add test for #13320 (561553fe) Message-ID: <20170505025440.59D403A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/561553fe424e2f2e3500b635655fe6d9c294c666/ghc >--------------------------------------------------------------- commit 561553fe424e2f2e3500b635655fe6d9c294c666 Author: David Feuer Date: Thu May 4 13:17:34 2017 -0400 Add test for #13320 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13320 Differential Revision: https://phabricator.haskell.org/D3532 (cherry picked from commit cb850e01560adf12e83fcf85f479636be17d017c) >--------------------------------------------------------------- 561553fe424e2f2e3500b635655fe6d9c294c666 testsuite/tests/typecheck/should_fail/T13320.hs | 32 ++++++++++++++++++++++ .../tests/typecheck/should_fail/T13320.stderr | 8 ++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 41 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T13320.hs b/testsuite/tests/typecheck/should_fail/T13320.hs new file mode 100644 index 0000000..d80dd4f --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T13320.hs @@ -0,0 +1,32 @@ +{-# language ConstraintKinds, FlexibleContexts, TypeFamilies, + UndecidableInstances, DeriveFunctor #-} + +module T13320 where + +import GHC.Exts (Constraint) + +data QCGen + +newtype Gen a = MkGen { unGen :: QCGen -> Int -> a } + deriving Functor + +sized :: (Int -> Gen a) -> Gen a +sized f = MkGen (\r n -> let MkGen m = f n in m r n) + +class Arbitrary a where + arbitrary :: Gen a + +type family X_Var ξ + +data TermX ξ = Var (X_Var ξ) + +type ForallX (φ :: * -> Constraint) ξ = ( φ (X_Var ξ) ) + +-- This type signature used to be necessary to prevent the +-- type checker from looping. +-- genTerm :: ForallX Arbitrary ξ => Int -> Gen (TermX ξ) +genTerm 0 = Var <$> arbitrary +genTerm n = Var <$> genTerm (n - 1) + +instance ForallX Arbitrary ξ => Arbitrary (TermX ξ) where + arbitrary = sized genTerm diff --git a/testsuite/tests/typecheck/should_fail/T13320.stderr b/testsuite/tests/typecheck/should_fail/T13320.stderr new file mode 100644 index 0000000..de783b0 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T13320.stderr @@ -0,0 +1,8 @@ + +T13320.hs:32:21: error: + • Couldn't match expected type ‘TermX ξ’ with actual type ‘X_Var ξ’ + • In the first argument of ‘sized’, namely ‘genTerm’ + In the expression: sized genTerm + In an equation for ‘arbitrary’: arbitrary = sized genTerm + • Relevant bindings include + arbitrary :: Gen (TermX ξ) (bound at T13320.hs:32:3) diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index e5c5e71..0dc4e1a 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -432,3 +432,4 @@ test('T13292', normal, multimod_compile, ['T13292', '-v0 -fdefer-type-errors']) test('T13300', normal, compile_fail, ['']) test('T12709', normal, compile_fail, ['']) test('T13446', normal, compile_fail, ['']) +test('T13320', normal, compile_fail, ['']) From git at git.haskell.org Fri May 5 02:54:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 May 2017 02:54:48 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Pass -ffrontend-opt arguments to frontend plugin in the correct order (771e8d6) Message-ID: <20170505025448.89C023A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/771e8d6838238fe87b2282696bff77fd4c474f71/ghc >--------------------------------------------------------------- commit 771e8d6838238fe87b2282696bff77fd4c474f71 Author: doug Date: Thu May 4 14:16:17 2017 -0400 Pass -ffrontend-opt arguments to frontend plugin in the correct order Previously they were passed in the reverse order that they're specified on the command line. Add a haddock to frontendPluginOpts in DynFlags.hs. Modify test frontend01 to cover the case of multiple -ffrontend-opt. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13632 Differential Revision: https://phabricator.haskell.org/D3520 (cherry picked from commit db10b79994f7728cbaaa906c6f6eda0b6783df29) >--------------------------------------------------------------- 771e8d6838238fe87b2282696bff77fd4c474f71 compiler/main/DynFlags.hs | 2 ++ ghc/Main.hs | 3 ++- testsuite/tests/plugins/Makefile | 2 +- testsuite/tests/plugins/frontend01.stdout | 2 +- 4 files changed, 6 insertions(+), 3 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 2773b87..10bf671 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -794,6 +794,8 @@ data DynFlags = DynFlags { pluginModNames :: [ModuleName], pluginModNameOpts :: [(ModuleName,String)], frontendPluginOpts :: [String], + -- ^ the @-ffrontend-opt@ flags given on the command line, in *reverse* + -- order that they're specified on the command line. -- GHC API hooks hooks :: Hooks, diff --git a/ghc/Main.hs b/ghc/Main.hs index 29012f6..cc6d08e 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -837,7 +837,8 @@ doFrontend modname _ = pluginError [modname] doFrontend modname srcs = do hsc_env <- getSession frontend_plugin <- liftIO $ loadFrontendPlugin hsc_env modname - frontend frontend_plugin (frontendPluginOpts (hsc_dflags hsc_env)) srcs + frontend frontend_plugin + (reverse $ frontendPluginOpts (hsc_dflags hsc_env)) srcs #endif -- ----------------------------------------------------------------------------- diff --git a/testsuite/tests/plugins/Makefile b/testsuite/tests/plugins/Makefile index 46fdc7d..efe17ef 100644 --- a/testsuite/tests/plugins/Makefile +++ b/testsuite/tests/plugins/Makefile @@ -34,7 +34,7 @@ T10294a: frontend01: $(RM) FrontendPlugin.hi FrontendPlugin.o frontend01 frontend01.hi frontend.o "$(TEST_HC)" $(TEST_HC_OPTS) $(ghcPluginWayFlags) -Wall -package ghc -c FrontendPlugin.hs - "$(TEST_HC)" $(TEST_HC_OPTS) $(ghcPluginWayFlags) --frontend FrontendPlugin -ffrontend-opt foobar frontend01 + "$(TEST_HC)" $(TEST_HC_OPTS) $(ghcPluginWayFlags) --frontend FrontendPlugin -ffrontend-opt foo -ffrontend-opt bar frontend01 ./frontend01 # -hide-all-plugin-packages + -package (this should not work!) diff --git a/testsuite/tests/plugins/frontend01.stdout b/testsuite/tests/plugins/frontend01.stdout index 84950bc..234c91c 100644 --- a/testsuite/tests/plugins/frontend01.stdout +++ b/testsuite/tests/plugins/frontend01.stdout @@ -1,4 +1,4 @@ -["foobar"] +["foo","bar"] [1 of 1] Compiling Main ( frontend01.hs, frontend01.o ) Linking frontend01 ... hello world From git at git.haskell.org Fri May 5 02:54:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 May 2017 02:54:45 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Add an Eq instance for UniqSet (c52495c) Message-ID: <20170505025445.C86413A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/c52495c8dba2e2c8479caa405f2410ca6e54a9bc/ghc >--------------------------------------------------------------- commit c52495c8dba2e2c8479caa405f2410ca6e54a9bc Author: David Feuer Date: Thu May 4 14:16:02 2017 -0400 Add an Eq instance for UniqSet I left that out by mistake, and it apparently breaks at least one existing plugin. Reviewers: christiaanb, austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3518 (cherry picked from commit a660844c0859b7a2e76c15f2fb4abec209afea90) >--------------------------------------------------------------- c52495c8dba2e2c8479caa405f2410ca6e54a9bc compiler/utils/UniqFM.hs | 17 +++++++++++++++++ compiler/utils/UniqSet.hs | 6 ++++++ 2 files changed, 23 insertions(+) diff --git a/compiler/utils/UniqFM.hs b/compiler/utils/UniqFM.hs index 8214f17..71a092b 100644 --- a/compiler/utils/UniqFM.hs +++ b/compiler/utils/UniqFM.hs @@ -55,6 +55,7 @@ module UniqFM ( intersectUFM, intersectUFM_C, disjointUFM, + equalKeysUFM, nonDetFoldUFM, foldUFM, nonDetFoldUFM_Directly, anyUFM, allUFM, seqEltsUFM, mapUFM, mapUFM_Directly, @@ -76,6 +77,11 @@ import Outputable import Data.List (foldl') import qualified Data.IntMap as M +#if MIN_VERSION_containers(0,5,9) +import qualified Data.IntMap.Merge.Lazy as M +import Control.Applicative (Const (..)) +import qualified Data.Monoid as Mon +#endif import qualified Data.IntSet as S import Data.Typeable import Data.Data @@ -339,6 +345,17 @@ nonDetUFMToList (UFM m) = map (\(k, v) -> (getUnique k, v)) $ M.toList m ufmToIntMap :: UniqFM elt -> M.IntMap elt ufmToIntMap (UFM m) = m +-- Determines whether two 'UniqFm's contain the same keys. +equalKeysUFM :: UniqFM a -> UniqFM b -> Bool +#if MIN_VERSION_containers(0,5,9) +equalKeysUFM (UFM m1) (UFM m2) = Mon.getAll $ getConst $ + M.mergeA (M.traverseMissing (\_ _ -> Const (Mon.All False))) + (M.traverseMissing (\_ _ -> Const (Mon.All False))) + (M.zipWithAMatched (\_ _ _ -> Const (Mon.All True))) m1 m2 +#else +equalKeysUFM (UFM m1) (UFM m2) = M.keys m1 == M.keys m2 +#endif + -- Instances #if __GLASGOW_HASKELL__ > 710 diff --git a/compiler/utils/UniqSet.hs b/compiler/utils/UniqSet.hs index ede900a..d9d51f4 100644 --- a/compiler/utils/UniqSet.hs +++ b/compiler/utils/UniqSet.hs @@ -128,6 +128,12 @@ mapUniqSet :: Uniquable b => (a -> b) -> UniqSet a -> UniqSet b -- the invariant. newtype UniqSet a = UniqSet {getUniqSet' :: UniqFM a} deriving Data + +-- Two 'UniqSet's are considered equal if they contain the same +-- uniques. +instance Eq (UniqSet a) where + UniqSet a == UniqSet b = equalKeysUFM a b + getUniqSet :: UniqSet a -> UniqFM a getUniqSet = getUniqSet' From git at git.haskell.org Fri May 5 02:54:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 May 2017 02:54:54 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix markdown for new GitHub Flavored Markdown (c7ab544) Message-ID: <20170505025454.1EB9D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/c7ab544db4626a43efa0876a0bf37ed2aa1de186/ghc >--------------------------------------------------------------- commit c7ab544db4626a43efa0876a0bf37ed2aa1de186 Author: Takenobu Tani Date: Thu May 4 14:19:37 2017 -0400 Fix markdown for new GitHub Flavored Markdown Delete whitespace between brackets. Because Github Flavored Markdown was changed [1]. [1]: https://githubengineering.com/a-formal-spec-for-github-markdown/ Test Plan: build Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3534 (cherry picked from commit 74f31539ce48a218922368ca62e1c3c6023f27a8) >--------------------------------------------------------------- c7ab544db4626a43efa0876a0bf37ed2aa1de186 README.md | 22 +++++++++++----------- 1 file changed, 11 insertions(+), 11 deletions(-) diff --git a/README.md b/README.md index 59f83bf..02bf4a8 100644 --- a/README.md +++ b/README.md @@ -29,7 +29,7 @@ There are two ways to get a source tree: $ git clone --recursive git://git.haskell.org/ghc.git Note: cloning GHC from Github requires a special setup. See [Getting a GHC - repository from Github] [7]. + repository from Github][7]. *See the GHC team's working conventions regarding [how to contribute a patch to GHC](http://ghc.haskell.org/trac/ghc/wiki/WorkingConventions/FixingBugs).* First time contributors are encouraged to get started by just sending a Pull Request. @@ -37,19 +37,19 @@ There are two ways to get a source tree: Building & Installing ===================== -For full information on building GHC, see the [GHC Building Guide] [3]. +For full information on building GHC, see the [GHC Building Guide][3]. Here follows a summary - if you get into trouble, the Building Guide has all the answers. Before building GHC you may need to install some other tools and -libraries. See, [Setting up your system for building GHC] [8]. +libraries. See, [Setting up your system for building GHC][8]. -*NB.* In particular, you need [GHC] [1] installed in order to build GHC, +*NB.* In particular, you need [GHC][1] installed in order to build GHC, because the compiler is itself written in Haskell. You also need -[Happy] [4], [Alex] [5], and [Cabal] [9]. For instructions on how -to port GHC to a new platform, see the [GHC Building Guide] [3]. +[Happy][4], [Alex][5], and [Cabal][9]. For instructions on how +to port GHC to a new platform, see the [GHC Building Guide][3]. -For building library documentation, you'll need [Haddock] [6]. To build +For building library documentation, you'll need [Haddock][6]. To build the compiler documentation, you need [Sphinx](http://www.sphinx-doc.org/) and Xelatex (only for PDF output). @@ -71,7 +71,7 @@ almost always a win regardless of how many cores you have. As a simple rule, you should have about N+1 jobs, where `N` is the amount of cores you have.) The `./boot` step is only necessary if this is a tree checked out -from git. For source distributions downloaded from [GHC's web site] [1], +from git. For source distributions downloaded from [GHC's web site][1], this step has already been performed. These steps give you the default build, which includes everything @@ -83,12 +83,12 @@ Filing bugs and feature requests If you've encountered what you believe is a bug in GHC, or you'd like to propose a feature request, please let us know! Submit a ticket in -our [bug tracker] [10] and we'll be sure to look into it. Remember: +our [bug tracker][10] and we'll be sure to look into it. Remember: **Filing a bug is the best way to make sure your issue isn't lost over time**, so please feel free. If you're an active user of GHC, you may also be interested in joining -the [glasgow-haskell-users] [11] mailing list, where developers and +the [glasgow-haskell-users][11] mailing list, where developers and GHC users discuss various topics and hang out. Hacking & Developing GHC @@ -103,7 +103,7 @@ Contributors & Acknowledgements =============================== GHC in its current form wouldn't exist without the hard work of -[its many contributors] [12]. Over time, it has grown to include the +[its many contributors][12]. Over time, it has grown to include the efforts and research of many institutions, highly talented people, and groups from around the world. We'd like to thank them all, and invite you to join! From git at git.haskell.org Fri May 5 02:54:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 May 2017 02:54:51 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix comment for compact region (26c041b) Message-ID: <20170505025451.45CD73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/26c041b694623d33bc5bac0534fbe7150042fdec/ghc >--------------------------------------------------------------- commit 26c041b694623d33bc5bac0534fbe7150042fdec Author: Takenobu Tani Date: Thu May 4 14:16:49 2017 -0400 Fix comment for compact region There were old module names: * Data.Compact -> GHC.Compact * Data.Compact.Internal -> GHC.Compact This commit is for ghc-8.2 branch. Test Plan: build Reviewers: austin, bgamari, hvr, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3522 (cherry picked from commit 4fcaf8e97db89b0c040ca33f0503faf3403b918f) >--------------------------------------------------------------- 26c041b694623d33bc5bac0534fbe7150042fdec libraries/base/GHC/IO/Exception.hs | 2 +- libraries/ghc-compact/GHC/Compact.hs | 4 ++-- rts/sm/CNF.c | 4 ++-- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/libraries/base/GHC/IO/Exception.hs b/libraries/base/GHC/IO/Exception.hs index 17eda3d..9203f46 100644 --- a/libraries/base/GHC/IO/Exception.hs +++ b/libraries/base/GHC/IO/Exception.hs @@ -131,7 +131,7 @@ allocationLimitExceeded = toException AllocationLimitExceeded -- | Compaction found an object that cannot be compacted. Functions -- cannot be compacted, nor can mutable objects or pinned objects. --- See 'Data.Compact.compact'. +-- See 'GHC.Compact.compact'. -- -- @since 4.10.0.0 newtype CompactionFailed = CompactionFailed String diff --git a/libraries/ghc-compact/GHC/Compact.hs b/libraries/ghc-compact/GHC/Compact.hs index ea0663e..375e341 100644 --- a/libraries/ghc-compact/GHC/Compact.hs +++ b/libraries/ghc-compact/GHC/Compact.hs @@ -104,12 +104,12 @@ import GHC.Types -- -- The cost of compaction is similar to the cost of GC for the same -- data, but it is performed only once. However, because --- "Data.Compact.compact" does not stop-the-world, retaining internal +-- "GHC.Compact.compact" does not stop-the-world, retaining internal -- sharing during the compaction process is very costly. The user -- can choose whether to 'compact' or 'compactWithSharing'. -- -- When you have a @'Compact' a@, you can get a pointer to the actual object --- in the region using "Data.Compact.getCompact". The 'Compact' type +-- in the region using "GHC.Compact.getCompact". The 'Compact' type -- serves as handle on the region itself; you can use this handle -- to add data to a specific 'Compact' with 'compactAdd' or -- 'compactAddWithSharing' (giving you a new handle which corresponds diff --git a/rts/sm/CNF.c b/rts/sm/CNF.c index ed9460e..fbebfab 100644 --- a/rts/sm/CNF.c +++ b/rts/sm/CNF.c @@ -4,7 +4,7 @@ * * GC support for immutable non-GCed structures, also known as Compact * Normal Forms (CNF for short). This provides the RTS support for - * the 'compact' package and the Data.Compact module. + * the 'compact' package and the GHC.Compact module. * * ---------------------------------------------------------------------------*/ @@ -51,7 +51,7 @@ Structure ~~~~~~~~~ - * In Data.Compact.Internal we have + * In GHC.Compact we have data Compact a = Compact Compact# a * The Compact# primitive object is operated on by the primitives. From git at git.haskell.org Fri May 5 02:54:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 May 2017 02:54:57 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Add regression test for #11616 (df44a60) Message-ID: <20170505025457.4C8D43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/df44a60a5b98490cf02b8b91f292de935e6da1df/ghc >--------------------------------------------------------------- commit df44a60a5b98490cf02b8b91f292de935e6da1df Author: Ryan Scott Date: Thu May 4 14:19:26 2017 -0400 Add regression test for #11616 The code in #11616 has been working for a while (ever since 8.0.1), so let's add a regression test for it to put the nail in the coffin. Test Plan: make test TEST=T11616 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #11616 Differential Revision: https://phabricator.haskell.org/D3531 (cherry picked from commit 03ca391f14f97486fd1c66d9c9d99686ae25cc10) >--------------------------------------------------------------- df44a60a5b98490cf02b8b91f292de935e6da1df testsuite/tests/polykinds/T11616.hs | 19 +++++++++++++++++++ testsuite/tests/polykinds/all.T | 1 + 2 files changed, 20 insertions(+) diff --git a/testsuite/tests/polykinds/T11616.hs b/testsuite/tests/polykinds/T11616.hs new file mode 100644 index 0000000..378032b --- /dev/null +++ b/testsuite/tests/polykinds/T11616.hs @@ -0,0 +1,19 @@ +{-# LANGUAGE AllowAmbiguousTypes #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE TypeInType #-} +module T11616 where + +class Whoami a where + whoami :: String + +instance Whoami Int where + whoami = "int" + +instance Whoami Bool where + whoami = "[y/n]" + +instance Whoami Maybe where + whoami = "call me maybe" + +whoisint :: String +whoisint = whoami @Int diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index 8684ec4..cb09629 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -140,6 +140,7 @@ test('T11362', normal, compile, ['-dunique-increment=-1']) # -dunique-increment=-1 doesn't work inside the file test('T11399', normal, compile_fail, ['']) test('T11611', normal, compile_fail, ['']) +test('T11616', normal, compile, ['']) test('T11648', normal, compile, ['']) test('T11648b', normal, compile_fail, ['']) test('KindVType', normal, compile_fail, ['']) From git at git.haskell.org Fri May 5 02:55:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 May 2017 02:55:00 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Implement sequential name lookup properly (0c84569) Message-ID: <20170505025500.626243A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/0c845697e054b5e30e76a801c7ebc78238c8268a/ghc >--------------------------------------------------------------- commit 0c845697e054b5e30e76a801c7ebc78238c8268a Author: Matthew Pickering Date: Thu May 4 14:15:43 2017 -0400 Implement sequential name lookup properly Previously we would run all the monadic actions and then combine their results. This caused problems if later actions raised errors but earlier lookups suceeded. We only want to run later lookups if the earlier ones fail. Fixes #13622 Reviewers: RyanGlScott, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #13622 Differential Revision: https://phabricator.haskell.org/D3515 (cherry picked from commit 1829d265662ca8d052df3e5df1aa1137b19e39ce) >--------------------------------------------------------------- 0c845697e054b5e30e76a801c7ebc78238c8268a compiler/typecheck/TcRnExports.hs | 26 +++++++++++++++++++------- testsuite/tests/module/T13622.hs | 5 +++++ testsuite/tests/module/all.T | 1 + 3 files changed, 25 insertions(+), 7 deletions(-) diff --git a/compiler/typecheck/TcRnExports.hs b/compiler/typecheck/TcRnExports.hs index 322de93..fa4b4bc 100644 --- a/compiler/typecheck/TcRnExports.hs +++ b/compiler/typecheck/TcRnExports.hs @@ -440,7 +440,7 @@ lookupChildrenExport parent rdr_items = let bareName = unLoc n lkup v = lookupExportChild parent (setRdrNameSpace bareName v) - name <- fmap mconcat . mapM lkup $ + name <- tryChildLookupResult $ map lkup $ (choosePossibleNamespaces (rdrNameSpace bareName)) -- Default to data constructors for slightly better error @@ -456,6 +456,17 @@ lookupChildrenExport parent rdr_items = FoundName name -> return $ Left (L (getLoc n) name) NameErr err_msg -> reportError err_msg >> failM +tryChildLookupResult :: [RnM ChildLookupResult] -> RnM ChildLookupResult +tryChildLookupResult [x] = x +tryChildLookupResult (x:xs) = do + res <- x + case res of + FoundFL {} -> return res + FoundName {} -> return res + NameErr {} -> return res + _ -> tryChildLookupResult xs +tryChildLookupResult _ = panic "tryChildLookupResult:empty list" + -- | Also captures the current context @@ -575,19 +586,20 @@ data DisambigInfo instance Monoid DisambigInfo where mempty = NoOccurrence -- This is the key line: We prefer disambiguated occurrences to other - -- names. - UniqueOccurrence _ `mappend` DisambiguatedOccurrence g' = DisambiguatedOccurrence g' - DisambiguatedOccurrence g' `mappend` UniqueOccurrence _ = DisambiguatedOccurrence g' + -- names. Notice that two disambiguated occurences are not ambiguous as + -- there is an internal invariant that a list of `DisambigInfo` arises + -- from a list of GREs which all have the same OccName. Thus, if we ever + -- have two DisambiguatedOccurences then they must have arisen from the + -- same GRE and hence it's safe to discard one. + _ `mappend` DisambiguatedOccurrence g' = DisambiguatedOccurrence g' + DisambiguatedOccurrence g' `mappend` _ = DisambiguatedOccurrence g' NoOccurrence `mappend` m = m m `mappend` NoOccurrence = m UniqueOccurrence g `mappend` UniqueOccurrence g' = AmbiguousOccurrence [g, g'] UniqueOccurrence g `mappend` AmbiguousOccurrence gs = AmbiguousOccurrence (g:gs) - DisambiguatedOccurrence g `mappend` DisambiguatedOccurrence g' = AmbiguousOccurrence [g, g'] - DisambiguatedOccurrence g `mappend` AmbiguousOccurrence gs = AmbiguousOccurrence (g:gs) AmbiguousOccurrence gs `mappend` UniqueOccurrence g' = AmbiguousOccurrence (g':gs) - AmbiguousOccurrence gs `mappend` DisambiguatedOccurrence g' = AmbiguousOccurrence (g':gs) AmbiguousOccurrence gs `mappend` AmbiguousOccurrence gs' = AmbiguousOccurrence (gs ++ gs') diff --git a/testsuite/tests/module/T13622.hs b/testsuite/tests/module/T13622.hs new file mode 100644 index 0000000..037283e --- /dev/null +++ b/testsuite/tests/module/T13622.hs @@ -0,0 +1,5 @@ +module Bug (Bits(Bits)) where + +import qualified Data.Bits as Bits + +newtype Bits = Bits Int diff --git a/testsuite/tests/module/all.T b/testsuite/tests/module/all.T index 6d05c77..5404f19 100644 --- a/testsuite/tests/module/all.T +++ b/testsuite/tests/module/all.T @@ -283,4 +283,5 @@ test('T11970A', [], multimod_compile, ['T11970A','-Wunused-imports']) test('T11970B', normal, compile_fail, ['']) test('MultiExport', normal, compile, ['']) test('T13528', normal, compile, ['']) +test('T13622', normal, compile, ['']) From git at git.haskell.org Fri May 5 02:55:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 May 2017 02:55:03 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: hpc: Output a legend at the top of output files (4a90910) Message-ID: <20170505025503.3BB9D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/4a90910a169bb1494ef38e45b0161680b3000691/ghc >--------------------------------------------------------------- commit 4a90910a169bb1494ef38e45b0161680b3000691 Author: Santiago Munin Date: Thu May 4 15:10:54 2017 -0400 hpc: Output a legend at the top of output files Updates hpc submodule. Reviewers: austin, bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #11799 Differential Revision: https://phabricator.haskell.org/D3465 (cherry picked from commit 8a2c2476b300969514888cb2084d083f8d18b6b0) >--------------------------------------------------------------- 4a90910a169bb1494ef38e45b0161680b3000691 libraries/hpc | 2 +- utils/hpc/HpcMarkup.hs | 7 +++++++ 2 files changed, 8 insertions(+), 1 deletion(-) diff --git a/libraries/hpc b/libraries/hpc index b28546c..1544cf0 160000 --- a/libraries/hpc +++ b/libraries/hpc @@ -1 +1 @@ -Subproject commit b28546ca003c6dbff586609a093e8c8091c34b14 +Subproject commit 1544cf04c38ab3b613dba1e0737de49c33321655 diff --git a/utils/hpc/HpcMarkup.hs b/utils/hpc/HpcMarkup.hs index fb68eac..ca30471 100644 --- a/utils/hpc/HpcMarkup.hs +++ b/utils/hpc/HpcMarkup.hs @@ -250,6 +250,13 @@ genHtmlFromMod dest_dir flags tix theFunTotals invertOutput = do "", "", "", + "
",
+                     concat [
+                         "",
+                         "never executed ",
+                         "always true ",
+                         "always false"],
+                     "
", "
"] ++ addLines content' ++ "\n
\n\n\n"; From git at git.haskell.org Fri May 5 10:26:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 May 2017 10:26:57 +0000 (UTC) Subject: [commit: ghc] master: Typos in comments [ci skip] (02748a5) Message-ID: <20170505102657.98CB93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/02748a52659949a06ef61d02894dadddd3c97412/ghc >--------------------------------------------------------------- commit 02748a52659949a06ef61d02894dadddd3c97412 Author: Gabor Greif Date: Thu May 4 18:33:57 2017 +0200 Typos in comments [ci skip] >--------------------------------------------------------------- 02748a52659949a06ef61d02894dadddd3c97412 compiler/basicTypes/OccName.hs | 2 +- compiler/llvmGen/LlvmCodeGen/Ppr.hs | 4 ++-- compiler/simplCore/FloatIn.hs | 2 +- compiler/stranal/DmdAnal.hs | 16 ++++++++-------- rts/RetainerSet.h | 2 +- rts/posix/itimer/Pthread.c | 2 +- testsuite/config/ghc | 2 +- testsuite/tests/indexed-types/should_compile/T3787.hs | 2 +- testsuite/tests/simplCore/should_compile/T8848.hs | 4 ++-- 9 files changed, 18 insertions(+), 18 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 02748a52659949a06ef61d02894dadddd3c97412 From git at git.haskell.org Fri May 5 10:40:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 May 2017 10:40:42 +0000 (UTC) Subject: [commit: ghc] master: tweak to minimize diff against ocInit_ELF (a483e71) Message-ID: <20170505104042.22E8A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a483e711da7834bc952367f554ac4e877b4e157a/ghc >--------------------------------------------------------------- commit a483e711da7834bc952367f554ac4e877b4e157a Author: Gabor Greif Date: Fri May 5 12:38:54 2017 +0200 tweak to minimize diff against ocInit_ELF >--------------------------------------------------------------- a483e711da7834bc952367f554ac4e877b4e157a rts/linker/MachO.c | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/rts/linker/MachO.c b/rts/linker/MachO.c index f8b665a..8895482 100644 --- a/rts/linker/MachO.c +++ b/rts/linker/MachO.c @@ -100,8 +100,8 @@ void ocInit_MachO(ObjectCode * oc) { oc->info = (struct ObjectCodeFormatInfo*)stgCallocBytes( - 1, sizeof(struct ObjectCodeFormatInfo), - "ocInit_MachO(struct ObjectCodeFormatInfo)"); + 1, sizeof *oc->info, + "ocInit_MachO(ObjectCodeFormatInfo)"); oc->info->header = (MachOHeader *) oc->image; oc->info->symCmd = NULL; oc->info->segCmd = NULL; From git at git.haskell.org Fri May 5 14:53:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 May 2017 14:53:23 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump Cabal submodule to 2.0.0.0 (fe5c821) Message-ID: <20170505145323.6A0313A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/fe5c821b2bded5ac6ddb17d94fdf66abe8a7952a/ghc >--------------------------------------------------------------- commit fe5c821b2bded5ac6ddb17d94fdf66abe8a7952a Author: Ben Gamari Date: Fri May 5 10:51:57 2017 -0400 Bump Cabal submodule to 2.0.0.0 >--------------------------------------------------------------- fe5c821b2bded5ac6ddb17d94fdf66abe8a7952a libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index b399b57..ece0273 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit b399b57bdfc0e3691148b441920298dd7ce28520 +Subproject commit ece0273b48b7ff19fff6cd82913717d86d3ffbfa From git at git.haskell.org Fri May 5 15:54:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 May 2017 15:54:00 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: CoreTidy: Don't seq unfoldings (febfbc5) Message-ID: <20170505155400.5C2983A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/febfbc5ad40915e5d6841d41e79f0ffed1370d61/ghc >--------------------------------------------------------------- commit febfbc5ad40915e5d6841d41e79f0ffed1370d61 Author: Ben Gamari Date: Tue May 2 11:36:47 2017 -0400 CoreTidy: Don't seq unfoldings Previously we would force uf_is_value and friends to ensure that we didn't retain a reference to the pre-tidying template, resulting in a space leak. Instead, we now just reinitialize these fields (despite the fact that they should not have changed). This may result in a bit more computation, but most of the time we won't ever evaluate them anyways, so the damage shouldn't be so bad. See #13564. (cherry picked from commit b3da6a6c3546562d5c5e83b8af5d3fd04c07e0c1) >--------------------------------------------------------------- febfbc5ad40915e5d6841d41e79f0ffed1370d61 compiler/coreSyn/CoreTidy.hs | 18 +++++++++++------- 1 file changed, 11 insertions(+), 7 deletions(-) diff --git a/compiler/coreSyn/CoreTidy.hs b/compiler/coreSyn/CoreTidy.hs index 89ce692..3578b0b 100644 --- a/compiler/coreSyn/CoreTidy.hs +++ b/compiler/coreSyn/CoreTidy.hs @@ -15,7 +15,7 @@ module CoreTidy ( #include "HsVersions.h" import CoreSyn -import CoreSeq ( seqUnfolding ) +import CoreUnfold ( mkCoreUnfolding ) import CoreArity import Id import IdInfo @@ -221,17 +221,21 @@ tidyUnfolding tidy_env df@(DFunUnfolding { df_bndrs = bndrs, df_args = args }) _ (tidy_env', bndrs') = tidyBndrs tidy_env bndrs tidyUnfolding tidy_env - unf@(CoreUnfolding { uf_tmpl = unf_rhs, uf_src = src }) + (CoreUnfolding { uf_tmpl = unf_rhs, uf_is_top = top_lvl + , uf_src = src, uf_guidance = guidance }) unf_from_rhs | isStableSource src - = seqIt $ unf { uf_tmpl = tidyExpr tidy_env unf_rhs } -- Preserves OccInfo - -- This seqIt avoids a space leak: otherwise the uf_is_value, - -- uf_is_conlike, ... fields may retain a reference to the - -- pre-tidied expression forever (ToIface doesn't look at them) + = mkCoreUnfolding src top_lvl (tidyExpr tidy_env unf_rhs) guidance + -- Preserves OccInfo + + -- Note that uf_is_value and friends may be a thunk containing a reference + -- to the old template. Consequently it is important that we rebuild them, + -- despite the fact that they won't change, to avoid a space leak (since, + -- e.g., ToIface doesn't look at them; see #13564). This is the same + -- approach we use in Simplify.simplUnfolding and TcIface.tcUnfolding. | otherwise = unf_from_rhs - where seqIt unf = seqUnfolding unf `seq` unf tidyUnfolding _ unf _ = unf -- NoUnfolding or OtherCon {- From git at git.haskell.org Fri May 5 15:54:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 May 2017 15:54:03 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: TcTypeable: Simplify (fb6936d) Message-ID: <20170505155403.116533A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/fb6936d5084887a402e5f9c74bdecaf77636d589/ghc >--------------------------------------------------------------- commit fb6936d5084887a402e5f9c74bdecaf77636d589 Author: Ben Gamari Date: Thu May 4 10:06:33 2017 -0400 TcTypeable: Simplify Simon pointed out that the zonk of the tyConKinds was redundant as tycon kinds will never contain mutable variables. This allows us to remove tycon_kind. Add a few commments clarifying the need to bring TyCon binders into scope before typechecking bindings. (cherry picked from commit c8e4d4b387d6d057dea98d6a595e3712f24289dc) >--------------------------------------------------------------- fb6936d5084887a402e5f9c74bdecaf77636d589 compiler/typecheck/TcTypeable.hs | 59 +++++++++++++++++++--------------------- 1 file changed, 28 insertions(+), 31 deletions(-) diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index d30a722..8d8ea03 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -16,7 +16,6 @@ import TyCoRep( Type(..), TyLit(..) ) import TcEnv import TcEvidence ( mkWpTyApps ) import TcRnMonad -import TcMType ( zonkTcType ) import HscTypes ( lookupId ) import PrelNames import TysPrim ( primTyCons ) @@ -209,11 +208,12 @@ mkModIdRHS mod * * ********************************************************************* -} --- | Information we need about a 'TyCon' to generate its representation. +-- | Information we need about a 'TyCon' to generate its representation. We +-- carry the 'Id' in order to share it between the generation of the @TyCon@ and +-- @KindRep@ bindings. data TypeableTyCon = TypeableTyCon { tycon :: !TyCon - , tycon_kind :: !Kind , tycon_rep_id :: !Id } @@ -224,7 +224,7 @@ data TypeRepTodo , pkg_fingerprint :: !Fingerprint -- ^ Package name fingerprint , mod_fingerprint :: !Fingerprint -- ^ Module name fingerprint , todo_tycons :: [TypeableTyCon] - -- ^ The 'TyCon's in need of bindings and their zonked kinds + -- ^ The 'TyCon's in need of bindings kinds } | ExportedKindRepsTodo [(Kind, Id)] -- ^ Build exported 'KindRep' bindings for the given set of kinds. @@ -232,30 +232,25 @@ data TypeRepTodo todoForTyCons :: Module -> Id -> [TyCon] -> TcM TypeRepTodo todoForTyCons mod mod_id tycons = do trTyConTy <- mkTyConTy <$> tcLookupTyCon trTyConTyConName - let mkRepId :: TyConRepName -> Id - mkRepId rep_name = mkExportedVanillaId rep_name trTyConTy - - tycons <- sequence - [ do kind <- zonkTcType $ tyConKind tc'' - return TypeableTyCon { tycon = tc'' - , tycon_kind = kind - , tycon_rep_id = mkRepId rep_name - } - | tc <- tycons - , tc' <- tc : tyConATs tc - -- If the tycon itself isn't typeable then we needn't look - -- at its promoted datacons as their kinds aren't Typeable - , Just _ <- pure $ tyConRepName_maybe tc' - -- We need type representations for any associated types - , let promoted = map promoteDataCon (tyConDataCons tc') - , tc'' <- tc' : promoted - , Just rep_name <- pure $ tyConRepName_maybe tc'' - ] - let typeable_tycons = filter is_typeable tycons - is_typeable (TypeableTyCon {..}) = - --pprTrace "todoForTycons" (ppr tycon $$ ppr bare_kind $$ ppr is_typeable) - (typeIsTypeable bare_kind) - where bare_kind = dropForAlls tycon_kind + let mk_rep_id :: TyConRepName -> Id + mk_rep_id rep_name = mkExportedVanillaId rep_name trTyConTy + + let typeable_tycons :: [TypeableTyCon] + typeable_tycons = + [ TypeableTyCon { tycon = tc'' + , tycon_rep_id = mk_rep_id rep_name + } + | tc <- tycons + , tc' <- tc : tyConATs tc + -- If the tycon itself isn't typeable then we needn't look + -- at its promoted datacons as their kinds aren't Typeable + , Just _ <- pure $ tyConRepName_maybe tc' + -- We need type representations for any associated types + , let promoted = map promoteDataCon (tyConDataCons tc') + , tc'' <- tc' : promoted + , Just rep_name <- pure $ tyConRepName_maybe tc'' + , typeIsTypeable $ dropForAlls $ tyConKind tc'' + ] return TypeRepTodo { mod_rep_expr = nlHsVar mod_id , pkg_fingerprint = pkg_fpr , mod_fingerprint = mod_fpr @@ -279,7 +274,9 @@ mkTypeRepTodoBinds todos -- First extend the type environment with all of the bindings -- which we are going to produce since we may need to refer to them - -- while generating the kind representations of other types. + -- while generating kind representations (namely, when we want to + -- represent a TyConApp in a kind, we must be able to look up the + -- TyCon associated with the applied type constructor). ; let produced_bndrs :: [Id] produced_bndrs = [ tycon_rep_id | todo@(TypeRepTodo{}) <- todos @@ -402,9 +399,9 @@ mkTyConRepBinds :: TypeableStuff -> TypeRepTodo -> TypeableTyCon -> KindRepM (LHsBinds Id) mkTyConRepBinds stuff@(Stuff {..}) todo (TypeableTyCon {..}) = do -- Make a KindRep - let (bndrs, kind) = splitForAllTyVarBndrs tycon_kind + let (bndrs, kind) = splitForAllTyVarBndrs (tyConKind tycon) liftTc $ traceTc "mkTyConKindRepBinds" - (ppr tycon $$ ppr tycon_kind $$ ppr kind) + (ppr tycon $$ ppr (tyConKind tycon) $$ ppr kind) let ctx = mkDeBruijnContext (map binderVar bndrs) kind_rep <- getKindRep stuff ctx kind From git at git.haskell.org Fri May 5 15:54:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 May 2017 15:54:06 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: testsuite: add new test for desugar warnings/errors with -fno-code (6723c2f) Message-ID: <20170505155406.7EBDA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/6723c2fdf3ce39227578d8da890969dc4ea836e7/ghc >--------------------------------------------------------------- commit 6723c2fdf3ce39227578d8da890969dc4ea836e7 Author: doug Date: Fri May 5 09:18:53 2017 -0400 testsuite: add new test for desugar warnings/errors with -fno-code Add a new (expect_broken) test T10600 that checks that the error: Top-level bindings for unlifted types aren't allowed: is thrown when compiling with -fno-code. This test currently fails because modules compiled with -fno-code aren't desugared. There are several other errors which can be thrown during desugaring that aren't tested for, discoverable by grepping for "errDs". Update .stderr files T8101 and T8101b. Presumably the compilation output has changed slightly since they were written. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #10600, #8101 Differential Revision: https://phabricator.haskell.org/D3533 (cherry picked from commit c326665c3742bb97904f7096689d40246ce6397f) >--------------------------------------------------------------- 6723c2fdf3ce39227578d8da890969dc4ea836e7 testsuite/tests/driver/T10600.hs | 10 ++++++++++ testsuite/tests/driver/T10600.stderr | 2 ++ testsuite/tests/driver/T8101.stderr | 3 +-- testsuite/tests/driver/T8101b.stderr | 3 ++- testsuite/tests/driver/all.T | 1 + 5 files changed, 16 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/driver/T10600.hs b/testsuite/tests/driver/T10600.hs new file mode 100644 index 0000000..86b6e6c --- /dev/null +++ b/testsuite/tests/driver/T10600.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE MagicHash #-} +module T10600 where + +import GHC.Prim + +-- This shouldn't compile as unlifted bindings aren't allowed at top-level. +-- However, #10600 described the situation where an error isn't throw when we +-- compile with -fno-code. +foo :: Int# +foo = 10600# diff --git a/testsuite/tests/driver/T10600.stderr b/testsuite/tests/driver/T10600.stderr new file mode 100644 index 0000000..4298e67 --- /dev/null +++ b/testsuite/tests/driver/T10600.stderr @@ -0,0 +1,2 @@ +T10600.hs:10:1: + Top-level bindings for unlifted types aren't allowed: foo = 10600# \ No newline at end of file diff --git a/testsuite/tests/driver/T8101.stderr b/testsuite/tests/driver/T8101.stderr index 6fda857..9f57360 100644 --- a/testsuite/tests/driver/T8101.stderr +++ b/testsuite/tests/driver/T8101.stderr @@ -1,5 +1,4 @@ - -T8101.hs:7:9: Warning: +T8101.hs:7:9: warning: [-Wincomplete-patterns (in -Wextra)] Pattern match(es) are non-exhaustive In a case alternative: Patterns not matched: diff --git a/testsuite/tests/driver/T8101b.stderr b/testsuite/tests/driver/T8101b.stderr index 555b036..ea8bcf0 100644 --- a/testsuite/tests/driver/T8101b.stderr +++ b/testsuite/tests/driver/T8101b.stderr @@ -1,5 +1,6 @@ +[1 of 1] Compiling A ( T8101b.hs, nothing ) -T8101b.hs:7:9: Warning: +T8101b.hs:7:9: warning: [-Wincomplete-patterns (in -Wextra)] Pattern match(es) are non-exhaustive In a case alternative: Patterns not matched: diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T index 09dc79a..7971d46 100644 --- a/testsuite/tests/driver/all.T +++ b/testsuite/tests/driver/all.T @@ -203,6 +203,7 @@ test('T2182', normal, run_command, ['$MAKE -s --no-print-directory T2182']) test('T8101', expect_broken(10600), compile, ['-Wall -fno-code']) test('T8101b', expect_broken(10600), multimod_compile, ['T8101b', '-Wall -fno-code']) +test('T10600', expect_broken(10600), compile_fail, ['-fno-code']) # Should not panic when compiling cmm file together with -outputdir. test('T9050', cmm_src, compile, ['-outputdir=.']) From git at git.haskell.org Sat May 6 16:39:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 16:39:03 +0000 (UTC) Subject: [commit: ghc] master: Add regression tests for #12947, #13640 (38a3819) Message-ID: <20170506163903.63EC53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/38a381912f67c0f6f3fba8de1026d7464826b851/ghc >--------------------------------------------------------------- commit 38a381912f67c0f6f3fba8de1026d7464826b851 Author: Ryan Scott Date: Sat May 6 12:31:40 2017 -0400 Add regression tests for #12947, #13640 Summary: Commit b4bdbe4957ae8b82c4cda5584203b44d3c4f004f (the fix for #12156) wound up being the fix for #12947 and #13640 as well. This adds regression tests for the latter two tickets to keep them fixed. Test Plan: make test TEST="T12947 T13640" Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #12947, #13640 Differential Revision: https://phabricator.haskell.org/D3528 >--------------------------------------------------------------- 38a381912f67c0f6f3fba8de1026d7464826b851 testsuite/tests/typecheck/should_fail/T12947.hs | 15 +++++++++++++++ testsuite/tests/typecheck/should_fail/T12947.stderr | 3 +++ testsuite/tests/typecheck/should_fail/T13640.hs | 13 +++++++++++++ testsuite/tests/typecheck/should_fail/T13640.stderr | 8 ++++++++ testsuite/tests/typecheck/should_fail/all.T | 2 ++ 5 files changed, 41 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T12947.hs b/testsuite/tests/typecheck/should_fail/T12947.hs new file mode 100644 index 0000000..d8a837c --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T12947.hs @@ -0,0 +1,15 @@ +{-# OPTIONS_GHC -dcore-lint -fdefer-typed-holes #-} +module T12947 where + +import qualified Control.Monad.Fail as Fail + +newtype P m a = P { unP :: (a -> IO (m ())) -> IO (m ()) } + +instance Functor (P m) where + +instance Applicative (P m) where + +instance Monad (P m) where + +instance (Fail.MonadFail m) => Fail.MonadFail (P m) where + fail msg = ContT $ \ _ -> Fail.fail msg diff --git a/testsuite/tests/typecheck/should_fail/T12947.stderr b/testsuite/tests/typecheck/should_fail/T12947.stderr new file mode 100644 index 0000000..a5d9193 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T12947.stderr @@ -0,0 +1,3 @@ + +T12947.hs:15:14: error: + Data constructor not in scope: ContT :: (p0 -> m0 a0) -> P m a diff --git a/testsuite/tests/typecheck/should_fail/T13640.hs b/testsuite/tests/typecheck/should_fail/T13640.hs new file mode 100644 index 0000000..be0faf7 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T13640.hs @@ -0,0 +1,13 @@ +{-# OPTIONS_GHC -dcore-lint -fdefer-typed-holes #-} +module T13640 where + +import Prelude hiding ((.)) + +class Functor' f where + map' :: (a -> b) -> f a -> f b + +class Bifunctor' f where + map2' :: (a -> b) -> f a c -> f b c + +bimap' :: Bifunctor' f => (a -> b) -> (c -> d) -> (f a c -> f b d) +bimap' f g = map2' f . map' diff --git a/testsuite/tests/typecheck/should_fail/T13640.stderr b/testsuite/tests/typecheck/should_fail/T13640.stderr new file mode 100644 index 0000000..d926dd9 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T13640.stderr @@ -0,0 +1,8 @@ + +T13640.hs:13:22: error: + • Variable not in scope: + (.) + :: (f0 a c0 -> f0 b c0) + -> ((a0 -> b0) -> f1 a0 -> f1 b0) -> f a c -> f b d + • Perhaps you want to remove ‘.’ from the explicit hiding list + in the import of ‘Prelude’ (T13640.hs:4:1-27). diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 3aa8cd5..4a409e0 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -422,6 +422,7 @@ test('T12837', normal, compile_fail, ['']) test('T12918a', normal, compile_fail, ['']) test('T12918b', normal, compile_fail, ['']) test('T12921', normal, compile_fail, ['']) +test('T12947', normal, compile_fail, ['']) test('T12973', normal, compile_fail, ['']) test('StrictBinds', normal, compile_fail, ['']) test('T13068', [extra_files(['T13068.hs', 'T13068a.hs', 'T13068.hs-boot', 'T13068m.hs'])], multimod_compile_fail, ['T13068m', '']) @@ -436,3 +437,4 @@ test('T13446', normal, compile_fail, ['']) test('T13506', normal, compile_fail, ['']) test('T13611', expect_broken(13611), compile_fail, ['']) test('T13320', normal, compile_fail, ['']) +test('T13640', normal, compile_fail, ['']) From git at git.haskell.org Sat May 6 16:39:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 16:39:06 +0000 (UTC) Subject: [commit: ghc] master: Add testsuite/timeout/TimeMe to .gitignore (4a6cb5e) Message-ID: <20170506163906.2060B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4a6cb5efe8e55717dfbbb677aa95e3b825d8de05/ghc >--------------------------------------------------------------- commit 4a6cb5efe8e55717dfbbb677aa95e3b825d8de05 Author: Ryan Scott Date: Sat May 6 12:34:36 2017 -0400 Add testsuite/timeout/TimeMe to .gitignore Summary: If you run `make test` on a non-Windows OS from a fresh build, the testsuite will create an executable called `TimeMe` which `git` thinks is an untracked file. Let's add it to `.gitignore` to avoid polluting the list of untracked files. Test Plan: Run `make test`, check if `TimeMe` is in the `git` untracked files Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3536 >--------------------------------------------------------------- 4a6cb5efe8e55717dfbbb677aa95e3b825d8de05 testsuite/.gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/testsuite/.gitignore b/testsuite/.gitignore index 2345ac4..21920ab 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -1628,4 +1628,5 @@ mk/ghcconfig*_test___spaces_ghc*.exe.mk /timeout/calibrate.out /timeout/dist/ /timeout/install-inplace/ +/timeout/TimeMe /tests/typecheck/should_run/T11049 From git at git.haskell.org Sat May 6 16:39:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 16:39:09 +0000 (UTC) Subject: [commit: ghc] master: Add regression test for #13651 (ed0c7f8) Message-ID: <20170506163909.524133A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ed0c7f8b1f91651203db4a0ee5931d47e1e6ab51/ghc >--------------------------------------------------------------- commit ed0c7f8b1f91651203db4a0ee5931d47e1e6ab51 Author: Ryan Scott Date: Sat May 6 12:37:00 2017 -0400 Add regression test for #13651 Commit eb55ec2941239dee05afc6be818b129efe51660e ended up fixing #13651, so let's add a regression test for it. >--------------------------------------------------------------- ed0c7f8b1f91651203db4a0ee5931d47e1e6ab51 testsuite/tests/typecheck/should_compile/T13651.hs | 14 ++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 15 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T13651.hs b/testsuite/tests/typecheck/should_compile/T13651.hs new file mode 100644 index 0000000..43ae633 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13651.hs @@ -0,0 +1,14 @@ +{-# LANGUAGE TypeFamilies, TypeFamilyDependencies #-} +module T13651 where + +type family F r s = f | f -> r s + +type instance F (Bar h (Foo r)) (Bar h (Foo s)) = Bar h (Bar r s) + +data Bar s b +data Foo a + +foo :: (F cr cu ~ Bar h (Bar r u), + F cu cs ~ Bar (Foo h) (Bar u s)) + => Bar h (Bar r u) -> Bar (Foo h) (Bar u s) -> Foo (cr -> cs) +foo = undefined diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 34b8184..6db86a8 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -558,3 +558,4 @@ test('T13526', normal, compile, ['']) test('T13603', normal, compile, ['']) test('T13333', normal, compile, ['']) test('T13585', [extra_files(['T13585.hs', 'T13585a.hs', 'T13585b.hs'])], run_command, ['$MAKE -s --no-print-directory T13585']) +test('T13651', normal, compile, ['']) From git at git.haskell.org Sat May 6 22:26:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:26:09 +0000 (UTC) Subject: [commit: ghc] branch 'wip/libdw-prof' created Message-ID: <20170506222609.643F03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/libdw-prof Referencing: e8461dde3cd1bbc6d68ef79bc338f660f1386709 From git at git.haskell.org Sat May 6 22:26:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:26:12 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: testsuite: Add config.libs_have_debug_info (e135024) Message-ID: <20170506222612.1E73C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/e1350246b7b718c5d2f95b8924145109cd1fdc7f/ghc >--------------------------------------------------------------- commit e1350246b7b718c5d2f95b8924145109cd1fdc7f Author: Ben Gamari Date: Sun Oct 25 19:13:53 2015 +0100 testsuite: Add config.libs_have_debug_info It's not entirely clear that this is the right way to do this since the compiler we are testing may not have the same configuration as the current tree. We could add a "Libraries have debugging information" entry to `ghc --info` but this seems rather heavy just for the testsuite. >--------------------------------------------------------------- e1350246b7b718c5d2f95b8924145109cd1fdc7f testsuite/driver/testlib.py | 3 +++ testsuite/mk/test.mk | 6 ++++++ 2 files changed, 9 insertions(+) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index ec0fc54..93a8f6e 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -410,6 +410,9 @@ def compiler_profiled( ): def rts_with_libdw( ): return config.rts_with_libdw +def libs_have_debug_info( ): + return config.libs_have_debug_info + def compiler_debugged( ): return config.compiler_debugged diff --git a/testsuite/mk/test.mk b/testsuite/mk/test.mk index a44e200..391883f 100644 --- a/testsuite/mk/test.mk +++ b/testsuite/mk/test.mk @@ -77,6 +77,12 @@ RUNTEST_OPTS += -e ghc_compiler_always_flags="'$(TEST_HC_OPTS)'" RUNTEST_OPTS += -e config.compiler_debugged=$(GhcDebugged) +ifeq "$(filter -g, $(GhcLibHcOps))" "-g" +RUNTEST_OPTS += -e libs_have_debug_info=1 +else +RUNTEST_OPTS += -e libs_have_debug_info=0 +endif + ifeq "$(GhcWithNativeCodeGen)" "YES" RUNTEST_OPTS += -e ghc_with_native_codegen=1 else From git at git.haskell.org Sat May 6 22:26:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:26:14 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Libdw: Reduce maximum backtrace depth (6a61f68) Message-ID: <20170506222614.CE4543A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/6a61f680e433e595b77e17fdf5e8581595acda97/ghc >--------------------------------------------------------------- commit 6a61f680e433e595b77e17fdf5e8581595acda97 Author: Ben Gamari Date: Mon Nov 21 21:50:55 2016 -0500 Libdw: Reduce maximum backtrace depth >--------------------------------------------------------------- 6a61f680e433e595b77e17fdf5e8581595acda97 rts/Libdw.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/Libdw.c b/rts/Libdw.c index 33a40a1..1e4f50e 100644 --- a/rts/Libdw.c +++ b/rts/Libdw.c @@ -16,7 +16,7 @@ #include #include -const int max_backtrace_depth = 5000; +const int max_backtrace_depth = 500; static BacktraceChunk *backtraceAllocChunk(BacktraceChunk *next) { BacktraceChunk *chunk = stgMallocBytes(sizeof(BacktraceChunk), From git at git.haskell.org Sat May 6 22:26:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:26:17 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: StgCmmForeign: Emit debug information for safe foreign calls (b589a93) Message-ID: <20170506222617.8B3BD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/b589a93b766028f19503f39355f515600da23042/ghc >--------------------------------------------------------------- commit b589a93b766028f19503f39355f515600da23042 Author: Ben Gamari Date: Mon Nov 21 23:33:56 2016 -0500 StgCmmForeign: Emit debug information for safe foreign calls Fixes #11338. >--------------------------------------------------------------- b589a93b766028f19503f39355f515600da23042 compiler/cmm/CmmLayoutStack.hs | 40 ++++++++++++++++-- compiler/codeGen/StgCmmForeign.hs | 86 ++++++++++++++++++++++++++++++++++++--- 2 files changed, 117 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 b589a93b766028f19503f39355f515600da23042 From git at git.haskell.org Sat May 6 22:26:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:26:20 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: libdw: testsuite infrastructure (439b1eb) Message-ID: <20170506222620.4D8B13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/439b1eb5b3e1517672572e569e88b49212831192/ghc >--------------------------------------------------------------- commit 439b1eb5b3e1517672572e569e88b49212831192 Author: Ben Gamari Date: Tue Sep 1 22:51:55 2015 +0200 libdw: testsuite infrastructure >--------------------------------------------------------------- 439b1eb5b3e1517672572e569e88b49212831192 testsuite/config/ghc | 4 ++++ testsuite/driver/testlib.py | 3 +++ 2 files changed, 7 insertions(+) diff --git a/testsuite/config/ghc b/testsuite/config/ghc index 6296394..102ae7d 100644 --- a/testsuite/config/ghc +++ b/testsuite/config/ghc @@ -13,6 +13,8 @@ config.hpc = 'hpc' config.gs = 'gs' config.confdir = '.' +config.libs_have_debug_info = libs_have_debug_info + # By default, the 'normal' and 'hpc' ways are enabled. In addition, certain # ways are enabled automatically if this GHC supports them. Ways that fall in # this group are 'optasm', 'optllvm', 'profasm', 'threaded1', 'threaded2', @@ -184,6 +186,8 @@ def get_compiler_info(): except: config.package_conf_cache_file = '' + config.rts_with_libdw = compilerInfoDict["RTS expects libdw"] == "YES" + # See Note [WayFlags] if config.ghc_dynamic: config.ghc_th_way_flags = "-dynamic" diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 1f08f5b..ec0fc54 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -407,6 +407,9 @@ def unregisterised( ): def compiler_profiled( ): return config.compiler_profiled +def rts_with_libdw( ): + return config.rts_with_libdw + def compiler_debugged( ): return config.compiler_debugged From git at git.haskell.org Sat May 6 22:26:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:26:23 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Temporarily commit dwarf flavour (30347d1) Message-ID: <20170506222623.8958A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/30347d1e072db4de5b6665f08cedbc10aeb63b0f/ghc >--------------------------------------------------------------- commit 30347d1e072db4de5b6665f08cedbc10aeb63b0f Author: Ben Gamari Date: Sun Jul 24 18:01:09 2016 +0200 Temporarily commit dwarf flavour >--------------------------------------------------------------- 30347d1e072db4de5b6665f08cedbc10aeb63b0f mk/flavours/dwarf.mk | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/mk/flavours/dwarf.mk b/mk/flavours/dwarf.mk new file mode 100644 index 0000000..6fd9cc7 --- /dev/null +++ b/mk/flavours/dwarf.mk @@ -0,0 +1,8 @@ +GhcStage1HcOpts += -DDEBUG +GhcStage2HcOpts += -DDEBUG +#GhcStage2HcOpts += -ddump-to-file -ddump-asm -ddump-cmm -dppr-debug +GhcLibHcOpts += -g +GhcLibHcOpts += -ddump-to-file -ddump-asm -ddump-cmm -ddump-debug -dppr-debug +GhcRtsHcOpts += -g +BUILD_PROF_LIBS = NO +DYNAMIC_GHC_PROGRAMS = NO From git at git.haskell.org Sat May 6 22:26:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:26:26 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: HACK: Disable substitution checks (6b79450) Message-ID: <20170506222626.4599E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/6b79450764e5cb6cd91310118e77903cc6409cc9/ghc >--------------------------------------------------------------- commit 6b79450764e5cb6cd91310118e77903cc6409cc9 Author: Ben Gamari Date: Mon Nov 21 23:08:40 2016 -0500 HACK: Disable substitution checks >--------------------------------------------------------------- 6b79450764e5cb6cd91310118e77903cc6409cc9 compiler/types/TyCoRep.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index 300ef80..cf757a9 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -2085,6 +2085,8 @@ isValidTCvSubst (TCvSubst in_scope tenv cenv) = -- Note [The substitution invariant]. checkValidSubst :: HasCallStack => TCvSubst -> [Type] -> [Coercion] -> a -> a checkValidSubst subst@(TCvSubst in_scope tenv cenv) tys cos a + | otherwise = a + | otherwise = ASSERT2( isValidTCvSubst subst, text "in_scope" <+> ppr in_scope $$ text "tenv" <+> ppr tenv $$ From git at git.haskell.org Sat May 6 22:26:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:26:29 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Debugging output (f11c85b) Message-ID: <20170506222629.11BB43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/f11c85b4f9d3e4476af6400c397ab764de23a659/ghc >--------------------------------------------------------------- commit f11c85b4f9d3e4476af6400c397ab764de23a659 Author: Ben Gamari Date: Mon Nov 21 22:26:13 2016 -0500 Debugging output >--------------------------------------------------------------- f11c85b4f9d3e4476af6400c397ab764de23a659 compiler/nativeGen/Dwarf.hs | 7 +++++++ compiler/nativeGen/Dwarf/Types.hs | 6 +++++- 2 files changed, 12 insertions(+), 1 deletion(-) diff --git a/compiler/nativeGen/Dwarf.hs b/compiler/nativeGen/Dwarf.hs index 1066169..497bb35 100644 --- a/compiler/nativeGen/Dwarf.hs +++ b/compiler/nativeGen/Dwarf.hs @@ -14,6 +14,8 @@ import Platform import Unique import UniqSupply +import ErrUtils + import Dwarf.Constants import Dwarf.Types @@ -89,6 +91,11 @@ dwarfGen df modLoc us blocks = do | otherwise = [DwarfARange lowLabel highLabel] let aranges = dwarfARangesSection $$ pprDwarfARanges aranges' unitU + let extractUnwinds blk = dblUnwind blk : foldMap extractUnwinds (dblBlocks blk) + dumpIfSet_dyn df Opt_D_dump_debug "Pre-dwarfGen" + (nest 4 $ vcat $ map (ppr . extractUnwinds) blocks) + dumpIfSet_dyn df Opt_D_dump_debug "Post-dwarfGen" + (nest 4 $ vcat $ foldMap (map ppr . extractUnwinds) procs) return (infoSct $$ abbrevSct $$ lineSct $$ frameSct $$ aranges, us'') -- | Build an address range entry for one proc. diff --git a/compiler/nativeGen/Dwarf/Types.hs b/compiler/nativeGen/Dwarf/Types.hs index d4d8e24..ebdbee3 100644 --- a/compiler/nativeGen/Dwarf/Types.hs +++ b/compiler/nativeGen/Dwarf/Types.hs @@ -264,6 +264,8 @@ data DwarfFrameProc , dwFdeBlocks :: [DwarfFrameBlock] -- ^ List of blocks. Order must match asm! } +instance Outputable DwarfFrameProc where + ppr x = ppr (dwFdeProc x) <> colon <+> hsep (map ppr $ dwFdeBlocks x) -- | Unwind instructions for a block. Will become part of the -- containing FDE. @@ -390,7 +392,9 @@ pprFrameBlock (DwarfFrameBlock hasInfo uws0) = if needsOffset then text "-1" else empty doc = sdocWithPlatform $ \plat -> pprByte dW_CFA_set_loc $$ pprWord lblDoc $$ - vcat (map (uncurry $ pprSetUnwind plat) changed) + vcat (map (uncurry $ pprSetUnwind' plat) changed) + pprSetUnwind' plat b c = + ifPprDebug (text "# "<+>ppr changed) $$ pprSetUnwind plat b c in (doc, uws) -- Note [Info Offset] From git at git.haskell.org Sat May 6 22:26:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:26:32 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Add test for DWARF unwinding through C stack (6ca9527) Message-ID: <20170506222632.746213A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/6ca9527f068adcfa59272b7a4756b30180ddc762/ghc >--------------------------------------------------------------- commit 6ca9527f068adcfa59272b7a4756b30180ddc762 Author: Ben Gamari Date: Fri Oct 23 11:37:36 2015 +0200 Add test for DWARF unwinding through C stack >--------------------------------------------------------------- 6ca9527f068adcfa59272b7a4756b30180ddc762 .../tests/codeGen/should_run/DwarfUnwindToC.hs | 21 +++++++++ .../tests/codeGen/should_run/DwarfUnwindToC.stdout | 52 ++++++++++++++++++++++ testsuite/tests/codeGen/should_run/all.T | 1 + 3 files changed, 74 insertions(+) diff --git a/testsuite/tests/codeGen/should_run/DwarfUnwindToC.hs b/testsuite/tests/codeGen/should_run/DwarfUnwindToC.hs new file mode 100644 index 0000000..52db325 --- /dev/null +++ b/testsuite/tests/codeGen/should_run/DwarfUnwindToC.hs @@ -0,0 +1,21 @@ +import GHC.ExecutionStack + +-- | Trim object file names +cleanUpBacktrace :: String -> String +cleanUpBacktrace = unlines . map trimLine . lines + where + trimLine (' ':'i':'n':' ':_) = "" + trimLine (x:xs) = x : trimLine xs + trimLine [] = [] + +test :: Int -> IO () +test 0 = return () +test i = do + print i + showStackTrace >>= putStrLn . cleanUpBacktrace + test (i-1) + return () + +main = do + test 3 + print "Hello" diff --git a/testsuite/tests/codeGen/should_run/DwarfUnwindToC.stdout b/testsuite/tests/codeGen/should_run/DwarfUnwindToC.stdout new file mode 100644 index 0000000..11c0967 --- /dev/null +++ b/testsuite/tests/codeGen/should_run/DwarfUnwindToC.stdout @@ -0,0 +1,52 @@ +3 +Stack trace: + set_initial_registers (rts/Libdw.c:278.0) + dwfl_thread_getframes + + dwfl_getthreads + dwfl_getthread_frames + libdw_get_backtrace (rts/Libdw.c:249.0) + base_GHCziExecutionStackziInternal_collectStackTrace1_info (libraries/base/GHC/ExecutionStack/Internal.hsc:194.1) + base_GHCziExecutionStack_showStackTrace1_info (libraries/base/GHC/ExecutionStack.hs:47.1) + base_GHCziBase_bindIO1_info (libraries/base/GHC/Base.hs:1081.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + stg_catch_frame_info (rts/Exception.cmm:370.1) + stg_stop_thread_info (rts/StgStartup.cmm:42.1) + +2 +Stack trace: + set_initial_registers (rts/Libdw.c:278.0) + dwfl_thread_getframes + + dwfl_getthreads + dwfl_getthread_frames + libdw_get_backtrace (rts/Libdw.c:249.0) + base_GHCziExecutionStackziInternal_collectStackTrace1_info (libraries/base/GHC/ExecutionStack/Internal.hsc:194.1) + base_GHCziExecutionStack_showStackTrace1_info (libraries/base/GHC/ExecutionStack.hs:47.1) + base_GHCziBase_bindIO1_info (libraries/base/GHC/Base.hs:1081.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + stg_catch_frame_info (rts/Exception.cmm:370.1) + stg_stop_thread_info (rts/StgStartup.cmm:42.1) + +1 +Stack trace: + set_initial_registers (rts/Libdw.c:278.0) + dwfl_thread_getframes + + dwfl_getthreads + dwfl_getthread_frames + libdw_get_backtrace (rts/Libdw.c:249.0) + base_GHCziExecutionStackziInternal_collectStackTrace1_info (libraries/base/GHC/ExecutionStack/Internal.hsc:194.1) + base_GHCziExecutionStack_showStackTrace1_info (libraries/base/GHC/ExecutionStack.hs:47.1) + base_GHCziBase_bindIO1_info (libraries/base/GHC/Base.hs:1081.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + stg_catch_frame_info (rts/Exception.cmm:370.1) + stg_stop_thread_info (rts/StgStartup.cmm:42.1) + +"Hello" diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 6318341..7f66f08 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -158,3 +158,4 @@ test('T9577', [ unless(arch('x86_64') or arch('i386'),skip), test('T13425', normal, compile_and_run, ['-O']) test('castFloatWord', normal, compile_and_run, ['-dcmm-lint']) +test('DwarfUnwindToC', [when(not rts_with_libdw() or not libs_have_debug_info(), skip)], compile_and_run, ['']) From git at git.haskell.org Sat May 6 22:26:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:26:38 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Add infrastructure for a simple statistical profiler (b6eb528) Message-ID: <20170506222638.EC2BD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/b6eb52809e7ff2c60c29480966cf1f46039db41f/ghc >--------------------------------------------------------------- commit b6eb52809e7ff2c60c29480966cf1f46039db41f Author: Ben Gamari Date: Fri Sep 25 18:32:05 2015 +0200 Add infrastructure for a simple statistical profiler >--------------------------------------------------------------- b6eb52809e7ff2c60c29480966cf1f46039db41f includes/rts/Config.h | 13 +++-- includes/rts/EventLogFormat.h | 4 +- rts/Trace.c | 13 +++++ rts/Trace.h | 12 +++++ rts/eventlog/EventLog.c | 118 ++++++++++++++++++++++++++++++++++++++++++ rts/eventlog/EventLog.h | 7 +++ 6 files changed, 159 insertions(+), 8 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 b6eb52809e7ff2c60c29480966cf1f46039db41f From git at git.haskell.org Sat May 6 22:26:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:26:36 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: rts: Emit debug information about program to event log (944d3d1) Message-ID: <20170506222636.377263A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/944d3d1b0a90c0a199c3a4c408de0a437e559a5b/ghc >--------------------------------------------------------------- commit 944d3d1b0a90c0a199c3a4c408de0a437e559a5b Author: Ben Gamari Date: Fri Sep 25 16:45:16 2015 +0200 rts: Emit debug information about program to event log This commit adds support to the RTS for traversing the debug information present in a program and emitting it to the event log for later consumption by debugging and performance analysis tools. This includes source note, symbol, and address range information derived from the DWARF annotations produced by GHC. Unfortunately one function necessary for traversing GHC's extended DWARF information, `dwarf_cu_getdwarf`, was only introduced in libdw 0.160. Consequently we won't be able to support statistical profiling in releases earlier than this. >--------------------------------------------------------------- 944d3d1b0a90c0a199c3a4c408de0a437e559a5b configure.ac | 7 ++ includes/rts/EventLogFormat.h | 9 +- rts/LibdwScrape.c | 287 ++++++++++++++++++++++++++++++++++++++++++ rts/LibdwScrape.h | 15 +++ rts/RtsStartup.c | 2 + rts/Trace.c | 24 ++++ rts/Trace.h | 19 ++- rts/eventlog/EventLog.c | 77 ++++++++++++ rts/eventlog/EventLog.h | 18 +++ 9 files changed, 456 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 944d3d1b0a90c0a199c3a4c408de0a437e559a5b From git at git.haskell.org Sat May 6 22:26:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:26:42 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: StatProfile: Heap and blackhole sampling (065fec9) Message-ID: <20170506222642.1B5E73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/065fec99d6a27a72a0455c09e50fdffd1e736a3a/ghc >--------------------------------------------------------------- commit 065fec99d6a27a72a0455c09e50fdffd1e736a3a Author: Ben Gamari Date: Sun Aug 30 16:54:15 2015 +0200 StatProfile: Heap and blackhole sampling Based on Peter Wortmann's c01384a26d7c9d22d26a760470bdb6379a2913ee. Lacking a better idea, I follow Peter's lead and hackily lay claim to R9 for funneling the attribution address to stg_gc_noregs. In addition I add support for profiling of blackhole wait events. >--------------------------------------------------------------- 065fec99d6a27a72a0455c09e50fdffd1e736a3a includes/rts/Config.h | 5 +++ rts/Capability.c | 20 ++++++++++++ rts/Capability.h | 9 ++++++ rts/HeapStackCheck.cmm | 74 +++++++++++++++++++++++++++++++++++++++++++ rts/Schedule.c | 3 ++ rts/StatProfile.h | 66 ++++++++++++++++++++++++++++++++++++++ rts/Trace.h | 2 ++ utils/deriveConstants/Main.hs | 4 +++ 8 files changed, 183 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 065fec99d6a27a72a0455c09e50fdffd1e736a3a From git at git.haskell.org Sat May 6 22:26:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:26:45 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Initial perf_event support (c908d0a) Message-ID: <20170506222645.B53AA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/c908d0af5f61f0b9d4de7388290263e0612b0735/ghc >--------------------------------------------------------------- commit c908d0af5f61f0b9d4de7388290263e0612b0735 Author: Ben Gamari Date: Sat Sep 26 20:32:52 2015 +0200 Initial perf_event support >--------------------------------------------------------------- c908d0af5f61f0b9d4de7388290263e0612b0735 configure.ac | 3 ++ distrib/configure.ac.in | 10 ++++ includes/rts/Config.h | 3 ++ mk/config.mk.in | 3 ++ rts/Capability.c | 10 ++++ rts/Capability.h | 5 ++ rts/PerfEvents.c | 127 ++++++++++++++++++++++++++++++++++++++++++++++++ rts/PerfEvents.h | 25 ++++++++++ rts/StatProfile.h | 39 ++++++++++++--- rts/Trace.h | 1 + 10 files changed, 218 insertions(+), 8 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 c908d0af5f61f0b9d4de7388290263e0612b0735 From git at git.haskell.org Sat May 6 22:26:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:26:48 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: StatProf: Add RTS flags to enable particular samplers (99506c3) Message-ID: <20170506222648.6AEE53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/99506c3d575ecd1a5fd0183992bb1593e89a71e6/ghc >--------------------------------------------------------------- commit 99506c3d575ecd1a5fd0183992bb1593e89a71e6 Author: Ben Gamari Date: Sun Nov 15 12:51:35 2015 +0100 StatProf: Add RTS flags to enable particular samplers >--------------------------------------------------------------- 99506c3d575ecd1a5fd0183992bb1593e89a71e6 includes/rts/Flags.h | 24 +++++++++++++++--------- rts/RtsFlags.c | 50 ++++++++++++++++++++++++++++++++++++++++++++++++-- rts/StatProfile.h | 2 ++ 3 files changed, 65 insertions(+), 11 deletions(-) diff --git a/includes/rts/Flags.h b/includes/rts/Flags.h index 6700f9d..3ae0f94 100644 --- a/includes/rts/Flags.h +++ b/includes/rts/Flags.h @@ -155,6 +155,11 @@ typedef struct _PROFILING_FLAGS { } PROFILING_FLAGS; +typedef struct _STAT_PROFILE_FLAGS { + bool heapCheckSampling; + bool blackholeSampling; +} STAT_PROFILE_FLAGS; + #define TRACE_NONE 0 #define TRACE_EVENTLOG 1 #define TRACE_STDERR 2 @@ -234,15 +239,16 @@ typedef struct _TICKY_FLAGS { /* See Note [Synchronization of flags and base APIs] */ typedef struct _RTS_FLAGS { /* The first portion of RTS_FLAGS is invariant. */ - GC_FLAGS GcFlags; - CONCURRENT_FLAGS ConcFlags; - MISC_FLAGS MiscFlags; - DEBUG_FLAGS DebugFlags; - COST_CENTRE_FLAGS CcFlags; - PROFILING_FLAGS ProfFlags; - TRACE_FLAGS TraceFlags; - TICKY_FLAGS TickyFlags; - PAR_FLAGS ParFlags; + GC_FLAGS GcFlags; + CONCURRENT_FLAGS ConcFlags; + MISC_FLAGS MiscFlags; + DEBUG_FLAGS DebugFlags; + COST_CENTRE_FLAGS CcFlags; + PROFILING_FLAGS ProfFlags; + STAT_PROFILE_FLAGS StatProfileFlags; + TRACE_FLAGS TraceFlags; + TICKY_FLAGS TickyFlags; + PAR_FLAGS ParFlags; } RTS_FLAGS; #if defined(COMPILING_RTS_MAIN) diff --git a/rts/RtsFlags.c b/rts/RtsFlags.c index b51d644..3693620 100644 --- a/rts/RtsFlags.c +++ b/rts/RtsFlags.c @@ -106,6 +106,7 @@ static bool read_heap_profiling_flag(const char *arg); #endif #if defined(TRACING) +static bool read_stat_profiler_flag(const char *arg); static void read_trace_flags(const char *arg); #endif @@ -203,6 +204,11 @@ void initRtsFlagsDefaults(void) RtsFlags.ProfFlags.bioSelector = NULL; #endif +#if defined(STAT_PROFILE) + RtsFlags.StatProfileFlags.blackholeSampling = false; + RtsFlags.StatProfileFlags.heapCheckSampling = false; +#endif + #if defined(TRACING) RtsFlags.TraceFlags.tracing = TRACE_NONE; RtsFlags.TraceFlags.timestamp = false; @@ -306,6 +312,15 @@ usage_text[] = { " -P More detailed Time/Allocation profile in tree format", " -Pa Give information about *all* cost centres in tree format", " -pj Output cost-center profile in JSON format", +#ifdef STAT_PROFILE +"", +" -pS" +" Enable recording of statistical profiler samples from", +" the given sample source. May be given multiple times.", +" The valid samplers are,", +" h = heap check (indicative of heap allocations)", +" b = black hole blocking (indicative of poor parallelism)", +#endif "", " -h Heap residency profile (hp2ps) (output file .hp)", " break-down: c = cost centre stack (default)", @@ -1058,8 +1073,21 @@ error = true; case 'P': /* detailed cost centre profiling (time/alloc) */ case 'p': /* cost centre profiling (time/alloc) */ OPTION_SAFE; - PROFILING_BUILD_ONLY( switch (rts_argv[arg][2]) { + case 's': +#ifdef TRACING + error = read_stat_profiler_flag(rts_argv[arg]); +#else + errorBelch( + "statistical profiling flag %s given but program was" + " not built with tracing. Build with -eventlog to use" + " statistical profiling.", + rts_argv[arg]); + error = true; +#endif + break; + + PROFILING_BUILD_ONLY( case 'a': RtsFlags.CcFlags.doCostCentres = COST_CENTRES_ALL; if (rts_argv[arg][3] != '\0') { @@ -1079,11 +1107,12 @@ error = true; RtsFlags.CcFlags.doCostCentres = COST_CENTRES_SUMMARY; } break; + ) default: unchecked_arg_start++; goto check_rest; } - ) break; + break; case 'R': OPTION_SAFE; @@ -1819,6 +1848,23 @@ static bool read_heap_profiling_flag(const char *arg) #endif #if defined(TRACING) +// Returns whether the parse resulted in an error. +static bool read_stat_profiler_flag(const char *arg) +{ + switch (arg[2]) { + case 'h': + RtsFlags.StatProfileFlags.heapCheckSampling = true; + break; + case 'b': + RtsFlags.StatProfileFlags.blackholeSampling = true; + break; + default: + errorBelch("Unknown statistical profiler sampler flag %s", arg); + return true; + } + return false; +} + static void read_trace_flags(const char *arg) { const char *c; diff --git a/rts/StatProfile.h b/rts/StatProfile.h index f1f0476..c7fc4e5 100644 --- a/rts/StatProfile.h +++ b/rts/StatProfile.h @@ -20,6 +20,7 @@ INLINE_HEADER void statProfileDumpHeapSamples(Capability *cap) { // See Note [Statistical profiling of heap allocations] + if (!RtsFlags.StatProfileFlags.heapCheckSampling) return; if (cap->heap_sample_count) { traceStatProfileSamples(cap, rtsTrue, SAMPLE_BY_HEAP_ALLOC, SAMPLE_TYPE_INSTR_PTR, @@ -33,6 +34,7 @@ INLINE_HEADER void statProfileDumpBlackholeSamples(Capability *cap) { // See Note [Statistical profiling of black-hole allocations] + if (!RtsFlags.StatProfileFlags.blackholeSampling) return; if (cap->blackhole_sample_count) { traceStatProfileSamples(cap, rtsTrue, SAMPLE_BY_BLACKHOLE, SAMPLE_TYPE_INSTR_PTR, From git at git.haskell.org Sat May 6 22:26:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:26:51 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: WIP (e8461dd) Message-ID: <20170506222651.1D4173A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/e8461dde3cd1bbc6d68ef79bc338f660f1386709/ghc >--------------------------------------------------------------- commit e8461dde3cd1bbc6d68ef79bc338f660f1386709 Author: Ben Gamari Date: Tue Dec 6 11:04:40 2016 -0500 WIP >--------------------------------------------------------------- e8461dde3cd1bbc6d68ef79bc338f660f1386709 docs/users_guide/eventlog-formats.rst | 35 +++++++++++++++++++++++++++++++++++ 1 file changed, 35 insertions(+) diff --git a/docs/users_guide/eventlog-formats.rst b/docs/users_guide/eventlog-formats.rst index 8d53f92..b826ad6 100644 --- a/docs/users_guide/eventlog-formats.rst +++ b/docs/users_guide/eventlog-formats.rst @@ -103,3 +103,38 @@ A variable-length event encoding a heap sample broken down by, * ``Word8``: Profile ID * ``Word64``: heap residency in bytes * ``String``: type or closure description, or module name + + +.. _statistical-profiler-formats: + +Statistical profiler formats +---------------------------- + +Samples +~~~~~~~ + +A block of samples from statistical profiling. A sample consists of a sample +value (e.g. an instruction pointer address) and a weight (e.g. how many times +the sample pointer was seen). + + * ``EVENT_STAT_PROF_SAMPLES`` (variable length) + * ``Word8``: Capability number + * ``Word8``: Sample trigger type + * ``Word8``: Sample value type + * Encoded samples + +The samples themselves are represented with a compressed encoding. Each sample +is represented by, + + * ``Word8``: Sample and weight encoding type + * top 4-bits: Sample encoding type + * ``0x0``: 8-bit positive offset to previous address + * ``0x1``: 8-bit negative offset to previous address + * ``0x4``: 32-bit positive offset to previous address + * ``0x5``: 32-bit negative offset to previous address + * ``0xf``: direct encoding + * bottom 4-bits: weight encoding type + * ``0``: ``weight == 1`` + * ``1``: weight encoded as ``Word8`` + * ``2``: weight encoded as ``Word16`` + * ``4``: weight encoded as ``Word32`` From git at git.haskell.org Sat May 6 22:40:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:40:10 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Debugging output (fffb23f) Message-ID: <20170506224010.434273A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/fffb23f9cbb386be16a1188aa181addf232c246d/ghc >--------------------------------------------------------------- commit fffb23f9cbb386be16a1188aa181addf232c246d Author: Ben Gamari Date: Mon Nov 21 22:26:13 2016 -0500 Debugging output >--------------------------------------------------------------- fffb23f9cbb386be16a1188aa181addf232c246d compiler/nativeGen/Dwarf.hs | 7 +++++++ compiler/nativeGen/Dwarf/Types.hs | 6 +++++- 2 files changed, 12 insertions(+), 1 deletion(-) diff --git a/compiler/nativeGen/Dwarf.hs b/compiler/nativeGen/Dwarf.hs index 1066169..497bb35 100644 --- a/compiler/nativeGen/Dwarf.hs +++ b/compiler/nativeGen/Dwarf.hs @@ -14,6 +14,8 @@ import Platform import Unique import UniqSupply +import ErrUtils + import Dwarf.Constants import Dwarf.Types @@ -89,6 +91,11 @@ dwarfGen df modLoc us blocks = do | otherwise = [DwarfARange lowLabel highLabel] let aranges = dwarfARangesSection $$ pprDwarfARanges aranges' unitU + let extractUnwinds blk = dblUnwind blk : foldMap extractUnwinds (dblBlocks blk) + dumpIfSet_dyn df Opt_D_dump_debug "Pre-dwarfGen" + (nest 4 $ vcat $ map (ppr . extractUnwinds) blocks) + dumpIfSet_dyn df Opt_D_dump_debug "Post-dwarfGen" + (nest 4 $ vcat $ foldMap (map ppr . extractUnwinds) procs) return (infoSct $$ abbrevSct $$ lineSct $$ frameSct $$ aranges, us'') -- | Build an address range entry for one proc. diff --git a/compiler/nativeGen/Dwarf/Types.hs b/compiler/nativeGen/Dwarf/Types.hs index d4d8e24..ebdbee3 100644 --- a/compiler/nativeGen/Dwarf/Types.hs +++ b/compiler/nativeGen/Dwarf/Types.hs @@ -264,6 +264,8 @@ data DwarfFrameProc , dwFdeBlocks :: [DwarfFrameBlock] -- ^ List of blocks. Order must match asm! } +instance Outputable DwarfFrameProc where + ppr x = ppr (dwFdeProc x) <> colon <+> hsep (map ppr $ dwFdeBlocks x) -- | Unwind instructions for a block. Will become part of the -- containing FDE. @@ -390,7 +392,9 @@ pprFrameBlock (DwarfFrameBlock hasInfo uws0) = if needsOffset then text "-1" else empty doc = sdocWithPlatform $ \plat -> pprByte dW_CFA_set_loc $$ pprWord lblDoc $$ - vcat (map (uncurry $ pprSetUnwind plat) changed) + vcat (map (uncurry $ pprSetUnwind' plat) changed) + pprSetUnwind' plat b c = + ifPprDebug (text "# "<+>ppr changed) $$ pprSetUnwind plat b c in (doc, uws) -- Note [Info Offset] From git at git.haskell.org Sat May 6 22:40:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:40:12 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Libdw: Reduce maximum backtrace depth (2071977) Message-ID: <20170506224012.EF0D73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/207197741798f04efb958b0595068e1254a26d40/ghc >--------------------------------------------------------------- commit 207197741798f04efb958b0595068e1254a26d40 Author: Ben Gamari Date: Mon Nov 21 21:50:55 2016 -0500 Libdw: Reduce maximum backtrace depth >--------------------------------------------------------------- 207197741798f04efb958b0595068e1254a26d40 rts/Libdw.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/Libdw.c b/rts/Libdw.c index 33a40a1..1e4f50e 100644 --- a/rts/Libdw.c +++ b/rts/Libdw.c @@ -16,7 +16,7 @@ #include #include -const int max_backtrace_depth = 5000; +const int max_backtrace_depth = 500; static BacktraceChunk *backtraceAllocChunk(BacktraceChunk *next) { BacktraceChunk *chunk = stgMallocBytes(sizeof(BacktraceChunk), From git at git.haskell.org Sat May 6 22:40:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:40:19 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Add infrastructure for a simple statistical profiler (179a382) Message-ID: <20170506224019.268A53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/179a3822b2c66d6928d137b7ab82746a1bde5959/ghc >--------------------------------------------------------------- commit 179a3822b2c66d6928d137b7ab82746a1bde5959 Author: Ben Gamari Date: Fri Sep 25 18:32:05 2015 +0200 Add infrastructure for a simple statistical profiler >--------------------------------------------------------------- 179a3822b2c66d6928d137b7ab82746a1bde5959 includes/rts/Config.h | 13 +++-- includes/rts/EventLogFormat.h | 4 +- rts/Trace.c | 13 +++++ rts/Trace.h | 12 +++++ rts/eventlog/EventLog.c | 118 ++++++++++++++++++++++++++++++++++++++++++ rts/eventlog/EventLog.h | 7 +++ 6 files changed, 159 insertions(+), 8 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 179a3822b2c66d6928d137b7ab82746a1bde5959 From git at git.haskell.org Sat May 6 22:40:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:40:16 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Add test for DWARF unwinding through C stack (d8b6ca8) Message-ID: <20170506224016.632A93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/d8b6ca8009fec92611eedf3ea3a196c4da34988f/ghc >--------------------------------------------------------------- commit d8b6ca8009fec92611eedf3ea3a196c4da34988f Author: Ben Gamari Date: Fri Oct 23 11:37:36 2015 +0200 Add test for DWARF unwinding through C stack >--------------------------------------------------------------- d8b6ca8009fec92611eedf3ea3a196c4da34988f .../tests/codeGen/should_run/DwarfUnwindToC.hs | 21 +++++++++ .../tests/codeGen/should_run/DwarfUnwindToC.stdout | 52 ++++++++++++++++++++++ testsuite/tests/codeGen/should_run/all.T | 1 + 3 files changed, 74 insertions(+) diff --git a/testsuite/tests/codeGen/should_run/DwarfUnwindToC.hs b/testsuite/tests/codeGen/should_run/DwarfUnwindToC.hs new file mode 100644 index 0000000..52db325 --- /dev/null +++ b/testsuite/tests/codeGen/should_run/DwarfUnwindToC.hs @@ -0,0 +1,21 @@ +import GHC.ExecutionStack + +-- | Trim object file names +cleanUpBacktrace :: String -> String +cleanUpBacktrace = unlines . map trimLine . lines + where + trimLine (' ':'i':'n':' ':_) = "" + trimLine (x:xs) = x : trimLine xs + trimLine [] = [] + +test :: Int -> IO () +test 0 = return () +test i = do + print i + showStackTrace >>= putStrLn . cleanUpBacktrace + test (i-1) + return () + +main = do + test 3 + print "Hello" diff --git a/testsuite/tests/codeGen/should_run/DwarfUnwindToC.stdout b/testsuite/tests/codeGen/should_run/DwarfUnwindToC.stdout new file mode 100644 index 0000000..11c0967 --- /dev/null +++ b/testsuite/tests/codeGen/should_run/DwarfUnwindToC.stdout @@ -0,0 +1,52 @@ +3 +Stack trace: + set_initial_registers (rts/Libdw.c:278.0) + dwfl_thread_getframes + + dwfl_getthreads + dwfl_getthread_frames + libdw_get_backtrace (rts/Libdw.c:249.0) + base_GHCziExecutionStackziInternal_collectStackTrace1_info (libraries/base/GHC/ExecutionStack/Internal.hsc:194.1) + base_GHCziExecutionStack_showStackTrace1_info (libraries/base/GHC/ExecutionStack.hs:47.1) + base_GHCziBase_bindIO1_info (libraries/base/GHC/Base.hs:1081.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + stg_catch_frame_info (rts/Exception.cmm:370.1) + stg_stop_thread_info (rts/StgStartup.cmm:42.1) + +2 +Stack trace: + set_initial_registers (rts/Libdw.c:278.0) + dwfl_thread_getframes + + dwfl_getthreads + dwfl_getthread_frames + libdw_get_backtrace (rts/Libdw.c:249.0) + base_GHCziExecutionStackziInternal_collectStackTrace1_info (libraries/base/GHC/ExecutionStack/Internal.hsc:194.1) + base_GHCziExecutionStack_showStackTrace1_info (libraries/base/GHC/ExecutionStack.hs:47.1) + base_GHCziBase_bindIO1_info (libraries/base/GHC/Base.hs:1081.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + stg_catch_frame_info (rts/Exception.cmm:370.1) + stg_stop_thread_info (rts/StgStartup.cmm:42.1) + +1 +Stack trace: + set_initial_registers (rts/Libdw.c:278.0) + dwfl_thread_getframes + + dwfl_getthreads + dwfl_getthread_frames + libdw_get_backtrace (rts/Libdw.c:249.0) + base_GHCziExecutionStackziInternal_collectStackTrace1_info (libraries/base/GHC/ExecutionStack/Internal.hsc:194.1) + base_GHCziExecutionStack_showStackTrace1_info (libraries/base/GHC/ExecutionStack.hs:47.1) + base_GHCziBase_bindIO1_info (libraries/base/GHC/Base.hs:1081.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + stg_catch_frame_info (rts/Exception.cmm:370.1) + stg_stop_thread_info (rts/StgStartup.cmm:42.1) + +"Hello" diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 6318341..7f66f08 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -158,3 +158,4 @@ test('T9577', [ unless(arch('x86_64') or arch('i386'),skip), test('T13425', normal, compile_and_run, ['-O']) test('castFloatWord', normal, compile_and_run, ['-dcmm-lint']) +test('DwarfUnwindToC', [when(not rts_with_libdw() or not libs_have_debug_info(), skip)], compile_and_run, ['']) From git at git.haskell.org Sat May 6 22:40:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:40:21 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: testsuite: Add config.libs_have_debug_info (07a3376) Message-ID: <20170506224021.D16343A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/07a3376ef8bbf377acfaa1f6161740f9af7a07f0/ghc >--------------------------------------------------------------- commit 07a3376ef8bbf377acfaa1f6161740f9af7a07f0 Author: Ben Gamari Date: Sun Oct 25 19:13:53 2015 +0100 testsuite: Add config.libs_have_debug_info It's not entirely clear that this is the right way to do this since the compiler we are testing may not have the same configuration as the current tree. We could add a "Libraries have debugging information" entry to `ghc --info` but this seems rather heavy just for the testsuite. >--------------------------------------------------------------- 07a3376ef8bbf377acfaa1f6161740f9af7a07f0 testsuite/driver/testlib.py | 3 +++ testsuite/mk/test.mk | 6 ++++++ 2 files changed, 9 insertions(+) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index ec0fc54..93a8f6e 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -410,6 +410,9 @@ def compiler_profiled( ): def rts_with_libdw( ): return config.rts_with_libdw +def libs_have_debug_info( ): + return config.libs_have_debug_info + def compiler_debugged( ): return config.compiler_debugged diff --git a/testsuite/mk/test.mk b/testsuite/mk/test.mk index a44e200..391883f 100644 --- a/testsuite/mk/test.mk +++ b/testsuite/mk/test.mk @@ -77,6 +77,12 @@ RUNTEST_OPTS += -e ghc_compiler_always_flags="'$(TEST_HC_OPTS)'" RUNTEST_OPTS += -e config.compiler_debugged=$(GhcDebugged) +ifeq "$(filter -g, $(GhcLibHcOps))" "-g" +RUNTEST_OPTS += -e libs_have_debug_info=1 +else +RUNTEST_OPTS += -e libs_have_debug_info=0 +endif + ifeq "$(GhcWithNativeCodeGen)" "YES" RUNTEST_OPTS += -e ghc_with_native_codegen=1 else From git at git.haskell.org Sat May 6 22:40:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:40:25 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: rts: Emit debug information about program to event log (5c19133) Message-ID: <20170506224025.A2C993A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/5c1913369b5c4510a877ff021ae3e88b15a72ecd/ghc >--------------------------------------------------------------- commit 5c1913369b5c4510a877ff021ae3e88b15a72ecd Author: Ben Gamari Date: Fri Sep 25 16:45:16 2015 +0200 rts: Emit debug information about program to event log This commit adds support to the RTS for traversing the debug information present in a program and emitting it to the event log for later consumption by debugging and performance analysis tools. This includes source note, symbol, and address range information derived from the DWARF annotations produced by GHC. Unfortunately one function necessary for traversing GHC's extended DWARF information, `dwarf_cu_getdwarf`, was only introduced in libdw 0.160. Consequently we won't be able to support statistical profiling in releases earlier than this. >--------------------------------------------------------------- 5c1913369b5c4510a877ff021ae3e88b15a72ecd configure.ac | 7 ++ includes/rts/EventLogFormat.h | 9 +- rts/LibdwScrape.c | 287 ++++++++++++++++++++++++++++++++++++++++++ rts/LibdwScrape.h | 15 +++ rts/RtsStartup.c | 2 + rts/Trace.c | 24 ++++ rts/Trace.h | 19 ++- rts/eventlog/EventLog.c | 77 ++++++++++++ rts/eventlog/EventLog.h | 18 +++ 9 files changed, 456 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 5c1913369b5c4510a877ff021ae3e88b15a72ecd From git at git.haskell.org Sat May 6 22:40:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:40:28 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: libdw: testsuite infrastructure (f5bb460) Message-ID: <20170506224028.5CE573A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/f5bb460b67e3962643f2500afa58f190e1932768/ghc >--------------------------------------------------------------- commit f5bb460b67e3962643f2500afa58f190e1932768 Author: Ben Gamari Date: Tue Sep 1 22:51:55 2015 +0200 libdw: testsuite infrastructure >--------------------------------------------------------------- f5bb460b67e3962643f2500afa58f190e1932768 testsuite/config/ghc | 4 ++++ testsuite/driver/testlib.py | 3 +++ 2 files changed, 7 insertions(+) diff --git a/testsuite/config/ghc b/testsuite/config/ghc index 6296394..102ae7d 100644 --- a/testsuite/config/ghc +++ b/testsuite/config/ghc @@ -13,6 +13,8 @@ config.hpc = 'hpc' config.gs = 'gs' config.confdir = '.' +config.libs_have_debug_info = libs_have_debug_info + # By default, the 'normal' and 'hpc' ways are enabled. In addition, certain # ways are enabled automatically if this GHC supports them. Ways that fall in # this group are 'optasm', 'optllvm', 'profasm', 'threaded1', 'threaded2', @@ -184,6 +186,8 @@ def get_compiler_info(): except: config.package_conf_cache_file = '' + config.rts_with_libdw = compilerInfoDict["RTS expects libdw"] == "YES" + # See Note [WayFlags] if config.ghc_dynamic: config.ghc_th_way_flags = "-dynamic" diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 1f08f5b..ec0fc54 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -407,6 +407,9 @@ def unregisterised( ): def compiler_profiled( ): return config.compiler_profiled +def rts_with_libdw( ): + return config.rts_with_libdw + def compiler_debugged( ): return config.compiler_debugged From git at git.haskell.org Sat May 6 22:40:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:40:31 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: StatProfile: Heap and blackhole sampling (e2ff03e) Message-ID: <20170506224031.8E7F13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/e2ff03e485acea1f88f8d462ac13bc2282fadd18/ghc >--------------------------------------------------------------- commit e2ff03e485acea1f88f8d462ac13bc2282fadd18 Author: Ben Gamari Date: Sun Aug 30 16:54:15 2015 +0200 StatProfile: Heap and blackhole sampling Based on Peter Wortmann's c01384a26d7c9d22d26a760470bdb6379a2913ee. Lacking a better idea, I follow Peter's lead and hackily lay claim to R9 for funneling the attribution address to stg_gc_noregs. In addition I add support for profiling of blackhole wait events. >--------------------------------------------------------------- e2ff03e485acea1f88f8d462ac13bc2282fadd18 includes/rts/Config.h | 5 +++ rts/Capability.c | 20 ++++++++++++ rts/Capability.h | 9 ++++++ rts/HeapStackCheck.cmm | 74 +++++++++++++++++++++++++++++++++++++++++++ rts/Schedule.c | 3 ++ rts/StatProfile.h | 66 ++++++++++++++++++++++++++++++++++++++ rts/Trace.h | 2 ++ utils/deriveConstants/Main.hs | 4 +++ 8 files changed, 183 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 e2ff03e485acea1f88f8d462ac13bc2282fadd18 From git at git.haskell.org Sat May 6 22:40:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:40:34 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: WIP (70055ad) Message-ID: <20170506224034.4AC083A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/70055add372e9486dae8bf0f7861ba653dc89d74/ghc >--------------------------------------------------------------- commit 70055add372e9486dae8bf0f7861ba653dc89d74 Author: Ben Gamari Date: Tue Dec 6 11:04:40 2016 -0500 WIP >--------------------------------------------------------------- 70055add372e9486dae8bf0f7861ba653dc89d74 docs/users_guide/eventlog-formats.rst | 35 +++++++++++++++++++++++++++++++++++ 1 file changed, 35 insertions(+) diff --git a/docs/users_guide/eventlog-formats.rst b/docs/users_guide/eventlog-formats.rst index 8d53f92..b826ad6 100644 --- a/docs/users_guide/eventlog-formats.rst +++ b/docs/users_guide/eventlog-formats.rst @@ -103,3 +103,38 @@ A variable-length event encoding a heap sample broken down by, * ``Word8``: Profile ID * ``Word64``: heap residency in bytes * ``String``: type or closure description, or module name + + +.. _statistical-profiler-formats: + +Statistical profiler formats +---------------------------- + +Samples +~~~~~~~ + +A block of samples from statistical profiling. A sample consists of a sample +value (e.g. an instruction pointer address) and a weight (e.g. how many times +the sample pointer was seen). + + * ``EVENT_STAT_PROF_SAMPLES`` (variable length) + * ``Word8``: Capability number + * ``Word8``: Sample trigger type + * ``Word8``: Sample value type + * Encoded samples + +The samples themselves are represented with a compressed encoding. Each sample +is represented by, + + * ``Word8``: Sample and weight encoding type + * top 4-bits: Sample encoding type + * ``0x0``: 8-bit positive offset to previous address + * ``0x1``: 8-bit negative offset to previous address + * ``0x4``: 32-bit positive offset to previous address + * ``0x5``: 32-bit negative offset to previous address + * ``0xf``: direct encoding + * bottom 4-bits: weight encoding type + * ``0``: ``weight == 1`` + * ``1``: weight encoded as ``Word8`` + * ``2``: weight encoded as ``Word16`` + * ``4``: weight encoded as ``Word32`` From git at git.haskell.org Sat May 6 22:40:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:40:40 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: StatProf: Add RTS flags to enable particular samplers (a899b21) Message-ID: <20170506224040.AD0D23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/a899b2112f9260ab601cda2678673289bdfc9879/ghc >--------------------------------------------------------------- commit a899b2112f9260ab601cda2678673289bdfc9879 Author: Ben Gamari Date: Sun Nov 15 12:51:35 2015 +0100 StatProf: Add RTS flags to enable particular samplers >--------------------------------------------------------------- a899b2112f9260ab601cda2678673289bdfc9879 includes/rts/Flags.h | 24 +++++++++++++++--------- rts/RtsFlags.c | 50 ++++++++++++++++++++++++++++++++++++++++++++++++-- rts/StatProfile.h | 2 ++ 3 files changed, 65 insertions(+), 11 deletions(-) diff --git a/includes/rts/Flags.h b/includes/rts/Flags.h index 6700f9d..3ae0f94 100644 --- a/includes/rts/Flags.h +++ b/includes/rts/Flags.h @@ -155,6 +155,11 @@ typedef struct _PROFILING_FLAGS { } PROFILING_FLAGS; +typedef struct _STAT_PROFILE_FLAGS { + bool heapCheckSampling; + bool blackholeSampling; +} STAT_PROFILE_FLAGS; + #define TRACE_NONE 0 #define TRACE_EVENTLOG 1 #define TRACE_STDERR 2 @@ -234,15 +239,16 @@ typedef struct _TICKY_FLAGS { /* See Note [Synchronization of flags and base APIs] */ typedef struct _RTS_FLAGS { /* The first portion of RTS_FLAGS is invariant. */ - GC_FLAGS GcFlags; - CONCURRENT_FLAGS ConcFlags; - MISC_FLAGS MiscFlags; - DEBUG_FLAGS DebugFlags; - COST_CENTRE_FLAGS CcFlags; - PROFILING_FLAGS ProfFlags; - TRACE_FLAGS TraceFlags; - TICKY_FLAGS TickyFlags; - PAR_FLAGS ParFlags; + GC_FLAGS GcFlags; + CONCURRENT_FLAGS ConcFlags; + MISC_FLAGS MiscFlags; + DEBUG_FLAGS DebugFlags; + COST_CENTRE_FLAGS CcFlags; + PROFILING_FLAGS ProfFlags; + STAT_PROFILE_FLAGS StatProfileFlags; + TRACE_FLAGS TraceFlags; + TICKY_FLAGS TickyFlags; + PAR_FLAGS ParFlags; } RTS_FLAGS; #if defined(COMPILING_RTS_MAIN) diff --git a/rts/RtsFlags.c b/rts/RtsFlags.c index b51d644..3693620 100644 --- a/rts/RtsFlags.c +++ b/rts/RtsFlags.c @@ -106,6 +106,7 @@ static bool read_heap_profiling_flag(const char *arg); #endif #if defined(TRACING) +static bool read_stat_profiler_flag(const char *arg); static void read_trace_flags(const char *arg); #endif @@ -203,6 +204,11 @@ void initRtsFlagsDefaults(void) RtsFlags.ProfFlags.bioSelector = NULL; #endif +#if defined(STAT_PROFILE) + RtsFlags.StatProfileFlags.blackholeSampling = false; + RtsFlags.StatProfileFlags.heapCheckSampling = false; +#endif + #if defined(TRACING) RtsFlags.TraceFlags.tracing = TRACE_NONE; RtsFlags.TraceFlags.timestamp = false; @@ -306,6 +312,15 @@ usage_text[] = { " -P More detailed Time/Allocation profile in tree format", " -Pa Give information about *all* cost centres in tree format", " -pj Output cost-center profile in JSON format", +#ifdef STAT_PROFILE +"", +" -pS" +" Enable recording of statistical profiler samples from", +" the given sample source. May be given multiple times.", +" The valid samplers are,", +" h = heap check (indicative of heap allocations)", +" b = black hole blocking (indicative of poor parallelism)", +#endif "", " -h Heap residency profile (hp2ps) (output file .hp)", " break-down: c = cost centre stack (default)", @@ -1058,8 +1073,21 @@ error = true; case 'P': /* detailed cost centre profiling (time/alloc) */ case 'p': /* cost centre profiling (time/alloc) */ OPTION_SAFE; - PROFILING_BUILD_ONLY( switch (rts_argv[arg][2]) { + case 's': +#ifdef TRACING + error = read_stat_profiler_flag(rts_argv[arg]); +#else + errorBelch( + "statistical profiling flag %s given but program was" + " not built with tracing. Build with -eventlog to use" + " statistical profiling.", + rts_argv[arg]); + error = true; +#endif + break; + + PROFILING_BUILD_ONLY( case 'a': RtsFlags.CcFlags.doCostCentres = COST_CENTRES_ALL; if (rts_argv[arg][3] != '\0') { @@ -1079,11 +1107,12 @@ error = true; RtsFlags.CcFlags.doCostCentres = COST_CENTRES_SUMMARY; } break; + ) default: unchecked_arg_start++; goto check_rest; } - ) break; + break; case 'R': OPTION_SAFE; @@ -1819,6 +1848,23 @@ static bool read_heap_profiling_flag(const char *arg) #endif #if defined(TRACING) +// Returns whether the parse resulted in an error. +static bool read_stat_profiler_flag(const char *arg) +{ + switch (arg[2]) { + case 'h': + RtsFlags.StatProfileFlags.heapCheckSampling = true; + break; + case 'b': + RtsFlags.StatProfileFlags.blackholeSampling = true; + break; + default: + errorBelch("Unknown statistical profiler sampler flag %s", arg); + return true; + } + return false; +} + static void read_trace_flags(const char *arg) { const char *c; diff --git a/rts/StatProfile.h b/rts/StatProfile.h index f1f0476..c7fc4e5 100644 --- a/rts/StatProfile.h +++ b/rts/StatProfile.h @@ -20,6 +20,7 @@ INLINE_HEADER void statProfileDumpHeapSamples(Capability *cap) { // See Note [Statistical profiling of heap allocations] + if (!RtsFlags.StatProfileFlags.heapCheckSampling) return; if (cap->heap_sample_count) { traceStatProfileSamples(cap, rtsTrue, SAMPLE_BY_HEAP_ALLOC, SAMPLE_TYPE_INSTR_PTR, @@ -33,6 +34,7 @@ INLINE_HEADER void statProfileDumpBlackholeSamples(Capability *cap) { // See Note [Statistical profiling of black-hole allocations] + if (!RtsFlags.StatProfileFlags.blackholeSampling) return; if (cap->blackhole_sample_count) { traceStatProfileSamples(cap, rtsTrue, SAMPLE_BY_BLACKHOLE, SAMPLE_TYPE_INSTR_PTR, From git at git.haskell.org Sat May 6 22:40:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 May 2017 22:40:37 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Initial perf_event support (ad190b4) Message-ID: <20170506224037.EF5613A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/ad190b4905e000d05d029226275cb42c1c062ffe/ghc >--------------------------------------------------------------- commit ad190b4905e000d05d029226275cb42c1c062ffe Author: Ben Gamari Date: Sat Sep 26 20:32:52 2015 +0200 Initial perf_event support >--------------------------------------------------------------- ad190b4905e000d05d029226275cb42c1c062ffe configure.ac | 3 ++ distrib/configure.ac.in | 10 ++++ includes/rts/Config.h | 3 ++ mk/config.mk.in | 3 ++ rts/Capability.c | 10 ++++ rts/Capability.h | 5 ++ rts/PerfEvents.c | 127 ++++++++++++++++++++++++++++++++++++++++++++++++ rts/PerfEvents.h | 25 ++++++++++ rts/StatProfile.h | 39 ++++++++++++--- rts/Trace.h | 1 + 10 files changed, 218 insertions(+), 8 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 ad190b4905e000d05d029226275cb42c1c062ffe From git at git.haskell.org Sun May 7 00:00:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 00:00:46 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: users-guide: Document statistical profiler eventlog records (1012110) Message-ID: <20170507000046.7C0D73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/10121101caac1c1070e31327efe25c72b2351347/ghc >--------------------------------------------------------------- commit 10121101caac1c1070e31327efe25c72b2351347 Author: Ben Gamari Date: Tue Dec 6 11:04:40 2016 -0500 users-guide: Document statistical profiler eventlog records >--------------------------------------------------------------- 10121101caac1c1070e31327efe25c72b2351347 docs/users_guide/eventlog-formats.rst | 35 +++++++++++++++++++++++++++++++++++ 1 file changed, 35 insertions(+) diff --git a/docs/users_guide/eventlog-formats.rst b/docs/users_guide/eventlog-formats.rst index 8d53f92..b826ad6 100644 --- a/docs/users_guide/eventlog-formats.rst +++ b/docs/users_guide/eventlog-formats.rst @@ -103,3 +103,38 @@ A variable-length event encoding a heap sample broken down by, * ``Word8``: Profile ID * ``Word64``: heap residency in bytes * ``String``: type or closure description, or module name + + +.. _statistical-profiler-formats: + +Statistical profiler formats +---------------------------- + +Samples +~~~~~~~ + +A block of samples from statistical profiling. A sample consists of a sample +value (e.g. an instruction pointer address) and a weight (e.g. how many times +the sample pointer was seen). + + * ``EVENT_STAT_PROF_SAMPLES`` (variable length) + * ``Word8``: Capability number + * ``Word8``: Sample trigger type + * ``Word8``: Sample value type + * Encoded samples + +The samples themselves are represented with a compressed encoding. Each sample +is represented by, + + * ``Word8``: Sample and weight encoding type + * top 4-bits: Sample encoding type + * ``0x0``: 8-bit positive offset to previous address + * ``0x1``: 8-bit negative offset to previous address + * ``0x4``: 32-bit positive offset to previous address + * ``0x5``: 32-bit negative offset to previous address + * ``0xf``: direct encoding + * bottom 4-bits: weight encoding type + * ``0``: ``weight == 1`` + * ``1``: weight encoded as ``Word8`` + * ``2``: weight encoded as ``Word16`` + * ``4``: weight encoded as ``Word32`` From git at git.haskell.org Sun May 7 00:00:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 00:00:49 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: fixup! Add infrastructure for a simple statistical profiler (04df437) Message-ID: <20170507000049.31E253A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/04df437bd3f0559062e52632e114c919d8b22216/ghc >--------------------------------------------------------------- commit 04df437bd3f0559062e52632e114c919d8b22216 Author: Ben Gamari Date: Sat May 6 19:42:48 2017 -0400 fixup! Add infrastructure for a simple statistical profiler >--------------------------------------------------------------- 04df437bd3f0559062e52632e114c919d8b22216 includes/rts/Config.h | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/includes/rts/Config.h b/includes/rts/Config.h index 52aa95f..10719bd 100644 --- a/includes/rts/Config.h +++ b/includes/rts/Config.h @@ -38,6 +38,11 @@ #endif #endif +/* Statistical profiler: implied by TRACING for the time being */ +#if defined(TRACING) +#define STAT_PROFILE +#endif + #if defined(STAT_PROFILE) #define STAT_PROFILE_HEAP_SAMPLE_BUFFER_SIZE 4096 #define STAT_PROFILE_BLACKHOLE_SAMPLE_BUFFER_SIZE 4096 From git at git.haskell.org Sun May 7 02:11:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 02:11:17 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: rts: Emit debug information about program to event log (b8c2692) Message-ID: <20170507021117.51DEB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/b8c269275ee4d8d4a58f0de23a4c5ff39ce0f352/ghc >--------------------------------------------------------------- commit b8c269275ee4d8d4a58f0de23a4c5ff39ce0f352 Author: Ben Gamari Date: Fri Sep 25 16:45:16 2015 +0200 rts: Emit debug information about program to event log This commit adds support to the RTS for traversing the debug information present in a program and emitting it to the event log for later consumption by debugging and performance analysis tools. This includes source note, symbol, and address range information derived from the DWARF annotations produced by GHC. Unfortunately one function necessary for traversing GHC's extended DWARF information, `dwarf_cu_getdwarf`, was only introduced in libdw 0.160. Consequently we won't be able to support statistical profiling in releases earlier than this. >--------------------------------------------------------------- b8c269275ee4d8d4a58f0de23a4c5ff39ce0f352 configure.ac | 7 ++ includes/rts/EventLogFormat.h | 9 +- rts/LibdwScrape.c | 287 ++++++++++++++++++++++++++++++++++++++++++ rts/LibdwScrape.h | 12 ++ rts/RtsStartup.c | 2 + rts/Trace.c | 24 ++++ rts/Trace.h | 19 ++- rts/eventlog/EventLog.c | 77 ++++++++++++ rts/eventlog/EventLog.h | 18 +++ 9 files changed, 453 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 b8c269275ee4d8d4a58f0de23a4c5ff39ce0f352 From git at git.haskell.org Sun May 7 02:11:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 02:11:20 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Add infrastructure for a simple statistical profiler (67f2ced) Message-ID: <20170507021120.15D803A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/67f2ced09a561acd85f9a7cd49dd9b0fe056e13e/ghc >--------------------------------------------------------------- commit 67f2ced09a561acd85f9a7cd49dd9b0fe056e13e Author: Ben Gamari Date: Fri Sep 25 18:32:05 2015 +0200 Add infrastructure for a simple statistical profiler >--------------------------------------------------------------- 67f2ced09a561acd85f9a7cd49dd9b0fe056e13e includes/rts/Config.h | 16 +++--- includes/rts/EventLogFormat.h | 4 +- rts/Trace.c | 13 +++++ rts/Trace.h | 12 +++++ rts/eventlog/EventLog.c | 118 ++++++++++++++++++++++++++++++++++++++++++ rts/eventlog/EventLog.h | 7 +++ 6 files changed, 163 insertions(+), 7 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 67f2ced09a561acd85f9a7cd49dd9b0fe056e13e From git at git.haskell.org Sun May 7 02:11:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 02:11:23 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: StatProfile: Heap and blackhole sampling (d9970b8) Message-ID: <20170507021123.394683A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/d9970b8e4e9cd3bdd2cccf024e520bc5edd6600a/ghc >--------------------------------------------------------------- commit d9970b8e4e9cd3bdd2cccf024e520bc5edd6600a Author: Ben Gamari Date: Sat May 6 20:58:12 2017 -0400 StatProfile: Heap and blackhole sampling Based on Peter Wortmann's c01384a26d7c9d22d26a760470bdb6379a2913ee. Lacking a better idea, I follow Peter's lead and hackily lay claim to R9 for funneling the attribution address to stg_gc_noregs. In addition I add support for profiling of blackhole wait events. >--------------------------------------------------------------- d9970b8e4e9cd3bdd2cccf024e520bc5edd6600a includes/rts/Config.h | 5 +++ rts/Capability.c | 20 ++++++++++++ rts/Capability.h | 9 ++++++ rts/HeapStackCheck.cmm | 74 +++++++++++++++++++++++++++++++++++++++++++ rts/Schedule.c | 3 ++ rts/StatProfile.h | 63 ++++++++++++++++++++++++++++++++++++ rts/Trace.h | 2 ++ utils/deriveConstants/Main.hs | 4 +++ 8 files changed, 180 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 d9970b8e4e9cd3bdd2cccf024e520bc5edd6600a From git at git.haskell.org Sun May 7 02:11:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 02:11:26 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Initial perf_event support (6dfe8c0) Message-ID: <20170507021126.DC04D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/6dfe8c0f65af112f61bbec8cdf4ff2d8d3ce1882/ghc >--------------------------------------------------------------- commit 6dfe8c0f65af112f61bbec8cdf4ff2d8d3ce1882 Author: Ben Gamari Date: Sat Sep 26 20:32:52 2015 +0200 Initial perf_event support >--------------------------------------------------------------- 6dfe8c0f65af112f61bbec8cdf4ff2d8d3ce1882 configure.ac | 3 ++ distrib/configure.ac.in | 10 ++++ includes/rts/Config.h | 3 ++ mk/config.mk.in | 3 ++ rts/Capability.c | 10 ++++ rts/Capability.h | 5 ++ rts/PerfEvents.c | 127 ++++++++++++++++++++++++++++++++++++++++++++++++ rts/PerfEvents.h | 27 ++++++++++ rts/StatProfile.h | 39 ++++++++++++--- rts/Trace.h | 1 + 10 files changed, 220 insertions(+), 8 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 6dfe8c0f65af112f61bbec8cdf4ff2d8d3ce1882 From git at git.haskell.org Sun May 7 02:11:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 02:11:29 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: users-guide: Document statistical profiler eventlog records (afd8fc4) Message-ID: <20170507021129.995183A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/afd8fc420baca22b7a2d4d1e6371d2803fb6d066/ghc >--------------------------------------------------------------- commit afd8fc420baca22b7a2d4d1e6371d2803fb6d066 Author: Ben Gamari Date: Tue Dec 6 11:04:40 2016 -0500 users-guide: Document statistical profiler eventlog records >--------------------------------------------------------------- afd8fc420baca22b7a2d4d1e6371d2803fb6d066 docs/users_guide/eventlog-formats.rst | 35 +++++++++++++++++++++++++++++++++++ 1 file changed, 35 insertions(+) diff --git a/docs/users_guide/eventlog-formats.rst b/docs/users_guide/eventlog-formats.rst index 8d53f92..b826ad6 100644 --- a/docs/users_guide/eventlog-formats.rst +++ b/docs/users_guide/eventlog-formats.rst @@ -103,3 +103,38 @@ A variable-length event encoding a heap sample broken down by, * ``Word8``: Profile ID * ``Word64``: heap residency in bytes * ``String``: type or closure description, or module name + + +.. _statistical-profiler-formats: + +Statistical profiler formats +---------------------------- + +Samples +~~~~~~~ + +A block of samples from statistical profiling. A sample consists of a sample +value (e.g. an instruction pointer address) and a weight (e.g. how many times +the sample pointer was seen). + + * ``EVENT_STAT_PROF_SAMPLES`` (variable length) + * ``Word8``: Capability number + * ``Word8``: Sample trigger type + * ``Word8``: Sample value type + * Encoded samples + +The samples themselves are represented with a compressed encoding. Each sample +is represented by, + + * ``Word8``: Sample and weight encoding type + * top 4-bits: Sample encoding type + * ``0x0``: 8-bit positive offset to previous address + * ``0x1``: 8-bit negative offset to previous address + * ``0x4``: 32-bit positive offset to previous address + * ``0x5``: 32-bit negative offset to previous address + * ``0xf``: direct encoding + * bottom 4-bits: weight encoding type + * ``0``: ``weight == 1`` + * ``1``: weight encoded as ``Word8`` + * ``2``: weight encoded as ``Word16`` + * ``4``: weight encoded as ``Word32`` From git at git.haskell.org Sun May 7 02:11:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 02:11:32 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: StatProf: Add RTS flags to enable particular samplers (96209b5) Message-ID: <20170507021132.5101A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/96209b5649118faa917bb05cce8b9d9bfab6549a/ghc >--------------------------------------------------------------- commit 96209b5649118faa917bb05cce8b9d9bfab6549a Author: Ben Gamari Date: Sun Nov 15 12:51:35 2015 +0100 StatProf: Add RTS flags to enable particular samplers >--------------------------------------------------------------- 96209b5649118faa917bb05cce8b9d9bfab6549a includes/rts/Flags.h | 24 +++++++++++++++--------- rts/RtsFlags.c | 50 ++++++++++++++++++++++++++++++++++++++++++++++++-- rts/StatProfile.h | 2 ++ 3 files changed, 65 insertions(+), 11 deletions(-) diff --git a/includes/rts/Flags.h b/includes/rts/Flags.h index 6700f9d..3ae0f94 100644 --- a/includes/rts/Flags.h +++ b/includes/rts/Flags.h @@ -155,6 +155,11 @@ typedef struct _PROFILING_FLAGS { } PROFILING_FLAGS; +typedef struct _STAT_PROFILE_FLAGS { + bool heapCheckSampling; + bool blackholeSampling; +} STAT_PROFILE_FLAGS; + #define TRACE_NONE 0 #define TRACE_EVENTLOG 1 #define TRACE_STDERR 2 @@ -234,15 +239,16 @@ typedef struct _TICKY_FLAGS { /* See Note [Synchronization of flags and base APIs] */ typedef struct _RTS_FLAGS { /* The first portion of RTS_FLAGS is invariant. */ - GC_FLAGS GcFlags; - CONCURRENT_FLAGS ConcFlags; - MISC_FLAGS MiscFlags; - DEBUG_FLAGS DebugFlags; - COST_CENTRE_FLAGS CcFlags; - PROFILING_FLAGS ProfFlags; - TRACE_FLAGS TraceFlags; - TICKY_FLAGS TickyFlags; - PAR_FLAGS ParFlags; + GC_FLAGS GcFlags; + CONCURRENT_FLAGS ConcFlags; + MISC_FLAGS MiscFlags; + DEBUG_FLAGS DebugFlags; + COST_CENTRE_FLAGS CcFlags; + PROFILING_FLAGS ProfFlags; + STAT_PROFILE_FLAGS StatProfileFlags; + TRACE_FLAGS TraceFlags; + TICKY_FLAGS TickyFlags; + PAR_FLAGS ParFlags; } RTS_FLAGS; #if defined(COMPILING_RTS_MAIN) diff --git a/rts/RtsFlags.c b/rts/RtsFlags.c index b51d644..e1cf8ea 100644 --- a/rts/RtsFlags.c +++ b/rts/RtsFlags.c @@ -106,6 +106,7 @@ static bool read_heap_profiling_flag(const char *arg); #endif #if defined(TRACING) +static bool read_stat_profiler_flag(const char *arg); static void read_trace_flags(const char *arg); #endif @@ -203,6 +204,11 @@ void initRtsFlagsDefaults(void) RtsFlags.ProfFlags.bioSelector = NULL; #endif +#if defined(STAT_PROFILE) + RtsFlags.StatProfileFlags.blackholeSampling = false; + RtsFlags.StatProfileFlags.heapCheckSampling = false; +#endif + #if defined(TRACING) RtsFlags.TraceFlags.tracing = TRACE_NONE; RtsFlags.TraceFlags.timestamp = false; @@ -306,6 +312,15 @@ usage_text[] = { " -P More detailed Time/Allocation profile in tree format", " -Pa Give information about *all* cost centres in tree format", " -pj Output cost-center profile in JSON format", +#if defined(STAT_PROFILE) +"", +" -pS" +" Enable recording of statistical profiler samples from", +" the given sample source. May be given multiple times.", +" The valid samplers are,", +" h = heap check (indicative of heap allocations)", +" b = black hole blocking (indicative of poor parallelism)", +#endif "", " -h Heap residency profile (hp2ps) (output file .hp)", " break-down: c = cost centre stack (default)", @@ -1058,8 +1073,21 @@ error = true; case 'P': /* detailed cost centre profiling (time/alloc) */ case 'p': /* cost centre profiling (time/alloc) */ OPTION_SAFE; - PROFILING_BUILD_ONLY( switch (rts_argv[arg][2]) { + case 's': +#if defined(TRACING) + error = read_stat_profiler_flag(rts_argv[arg]); +#else + errorBelch( + "statistical profiling flag %s given but program was" + " not built with tracing. Build with -eventlog to use" + " statistical profiling.", + rts_argv[arg]); + error = true; +#endif + break; + + PROFILING_BUILD_ONLY( case 'a': RtsFlags.CcFlags.doCostCentres = COST_CENTRES_ALL; if (rts_argv[arg][3] != '\0') { @@ -1079,11 +1107,12 @@ error = true; RtsFlags.CcFlags.doCostCentres = COST_CENTRES_SUMMARY; } break; + ) default: unchecked_arg_start++; goto check_rest; } - ) break; + break; case 'R': OPTION_SAFE; @@ -1819,6 +1848,23 @@ static bool read_heap_profiling_flag(const char *arg) #endif #if defined(TRACING) +// Returns whether the parse resulted in an error. +static bool read_stat_profiler_flag(const char *arg) +{ + switch (arg[2]) { + case 'h': + RtsFlags.StatProfileFlags.heapCheckSampling = true; + break; + case 'b': + RtsFlags.StatProfileFlags.blackholeSampling = true; + break; + default: + errorBelch("Unknown statistical profiler sampler flag %s", arg); + return true; + } + return false; +} + static void read_trace_flags(const char *arg) { const char *c; diff --git a/rts/StatProfile.h b/rts/StatProfile.h index 4a44cbb..8540c06 100644 --- a/rts/StatProfile.h +++ b/rts/StatProfile.h @@ -19,6 +19,7 @@ INLINE_HEADER void statProfileDumpHeapSamples(Capability *cap) { // See Note [Statistical profiling of heap allocations] + if (!RtsFlags.StatProfileFlags.heapCheckSampling) return; if (cap->heap_sample_count) { traceStatProfileSamples(cap, true, SAMPLE_BY_HEAP_ALLOC, SAMPLE_TYPE_INSTR_PTR, @@ -32,6 +33,7 @@ INLINE_HEADER void statProfileDumpBlackholeSamples(Capability *cap) { // See Note [Statistical profiling of black-hole allocations] + if (!RtsFlags.StatProfileFlags.blackholeSampling) return; if (cap->blackhole_sample_count) { traceStatProfileSamples(cap, true, SAMPLE_BY_BLACKHOLE, SAMPLE_TYPE_INSTR_PTR, From git at git.haskell.org Sun May 7 16:29:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 16:29:31 +0000 (UTC) Subject: [commit: ghc] master: base: Fix documentation for forkIOWithUnmask (1840121) Message-ID: <20170507162931.41BCD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1840121078718fb2a2fe5a7895501100517f627c/ghc >--------------------------------------------------------------- commit 1840121078718fb2a2fe5a7895501100517f627c Author: Ben Gamari Date: Fri May 5 16:47:00 2017 -0400 base: Fix documentation for forkIOWithUnmask forkIOUnmasked has been deprecated for several years now. Update reference to it. See #4858 and #5546. >--------------------------------------------------------------- 1840121078718fb2a2fe5a7895501100517f627c libraries/base/GHC/IO.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/GHC/IO.hs b/libraries/base/GHC/IO.hs index 63b47ff..118ebea 100644 --- a/libraries/base/GHC/IO.hs +++ b/libraries/base/GHC/IO.hs @@ -335,7 +335,7 @@ onException io what = io `catchException` \e -> do _ <- what -- use @mask_ $ forkIO ... at . This is particularly useful if you need -- to establish an exception handler in the forked thread before any -- asynchronous exceptions are received. To create a a new thread in --- an unmasked state use 'Control.Concurrent.forkIOUnmasked'. +-- an unmasked state use 'Control.Concurrent.forkIOWithUnmask'. -- mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b From git at git.haskell.org Sun May 7 16:29:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 16:29:33 +0000 (UTC) Subject: [commit: ghc] master: Bump Cabal submodule to the 2.0.0.0 tag (579749d) Message-ID: <20170507162933.E80B93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/579749d4c74b75d8f5df83234414b92950aca64b/ghc >--------------------------------------------------------------- commit 579749d4c74b75d8f5df83234414b92950aca64b Author: Ben Gamari Date: Sun May 7 11:26:25 2017 -0400 Bump Cabal submodule to the 2.0.0.0 tag >--------------------------------------------------------------- 579749d4c74b75d8f5df83234414b92950aca64b libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index 41f416b..ece0273 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 41f416bc27796a3dc87037b66b6fef6f5810bc77 +Subproject commit ece0273b48b7ff19fff6cd82913717d86d3ffbfa From git at git.haskell.org Sun May 7 16:29:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 16:29:37 +0000 (UTC) Subject: [commit: ghc] master: testsuite: add new test for desugar warnings/errors with -fno-code (baa18de) Message-ID: <20170507162937.6D7643A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/baa18def0da17f11497fecc6fe440cf125b50878/ghc >--------------------------------------------------------------- commit baa18def0da17f11497fecc6fe440cf125b50878 Author: doug Date: Fri May 5 09:18:53 2017 -0400 testsuite: add new test for desugar warnings/errors with -fno-code Add a new (expect_broken) test T10600 that checks that the error: Top-level bindings for unlifted types aren't allowed: is thrown when compiling with -fno-code. This test currently fails because modules compiled with -fno-code aren't desugared. There are several other errors which can be thrown during desugaring that aren't tested for, discoverable by grepping for "errDs". Update .stderr files T8101 and T8101b. Presumably the compilation output has changed slightly since they were written. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #10600, #8101 Differential Revision: https://phabricator.haskell.org/D3533 >--------------------------------------------------------------- baa18def0da17f11497fecc6fe440cf125b50878 testsuite/tests/driver/T10600.hs | 10 ++++++++++ testsuite/tests/driver/T10600.stderr | 2 ++ testsuite/tests/driver/T8101.stderr | 3 +-- testsuite/tests/driver/T8101b.stderr | 3 ++- testsuite/tests/driver/all.T | 1 + 5 files changed, 16 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/driver/T10600.hs b/testsuite/tests/driver/T10600.hs new file mode 100644 index 0000000..86b6e6c --- /dev/null +++ b/testsuite/tests/driver/T10600.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE MagicHash #-} +module T10600 where + +import GHC.Prim + +-- This shouldn't compile as unlifted bindings aren't allowed at top-level. +-- However, #10600 described the situation where an error isn't throw when we +-- compile with -fno-code. +foo :: Int# +foo = 10600# diff --git a/testsuite/tests/driver/T10600.stderr b/testsuite/tests/driver/T10600.stderr new file mode 100644 index 0000000..4298e67 --- /dev/null +++ b/testsuite/tests/driver/T10600.stderr @@ -0,0 +1,2 @@ +T10600.hs:10:1: + Top-level bindings for unlifted types aren't allowed: foo = 10600# \ No newline at end of file diff --git a/testsuite/tests/driver/T8101.stderr b/testsuite/tests/driver/T8101.stderr index 6fda857..9f57360 100644 --- a/testsuite/tests/driver/T8101.stderr +++ b/testsuite/tests/driver/T8101.stderr @@ -1,5 +1,4 @@ - -T8101.hs:7:9: Warning: +T8101.hs:7:9: warning: [-Wincomplete-patterns (in -Wextra)] Pattern match(es) are non-exhaustive In a case alternative: Patterns not matched: diff --git a/testsuite/tests/driver/T8101b.stderr b/testsuite/tests/driver/T8101b.stderr index 555b036..ea8bcf0 100644 --- a/testsuite/tests/driver/T8101b.stderr +++ b/testsuite/tests/driver/T8101b.stderr @@ -1,5 +1,6 @@ +[1 of 1] Compiling A ( T8101b.hs, nothing ) -T8101b.hs:7:9: Warning: +T8101b.hs:7:9: warning: [-Wincomplete-patterns (in -Wextra)] Pattern match(es) are non-exhaustive In a case alternative: Patterns not matched: diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T index 09dc79a..7971d46 100644 --- a/testsuite/tests/driver/all.T +++ b/testsuite/tests/driver/all.T @@ -203,6 +203,7 @@ test('T2182', normal, run_command, ['$MAKE -s --no-print-directory T2182']) test('T8101', expect_broken(10600), compile, ['-Wall -fno-code']) test('T8101b', expect_broken(10600), multimod_compile, ['T8101b', '-Wall -fno-code']) +test('T10600', expect_broken(10600), compile_fail, ['-fno-code']) # Should not panic when compiling cmm file together with -outputdir. test('T9050', cmm_src, compile, ['-outputdir=.']) From git at git.haskell.org Sun May 7 18:33:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 18:33:08 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: base: Fix documentation for forkIOWithUnmask (1cd69b9) Message-ID: <20170507183308.0A9FD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/1cd69b9b9d91e28ac2e60d902f0c5d4d9f51ca0f/ghc >--------------------------------------------------------------- commit 1cd69b9b9d91e28ac2e60d902f0c5d4d9f51ca0f Author: Ben Gamari Date: Fri May 5 16:47:00 2017 -0400 base: Fix documentation for forkIOWithUnmask forkIOUnmasked has been deprecated for several years now. Update reference to it. See #4858 and #5546. (cherry picked from commit 1840121078718fb2a2fe5a7895501100517f627c) >--------------------------------------------------------------- 1cd69b9b9d91e28ac2e60d902f0c5d4d9f51ca0f libraries/base/GHC/IO.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/GHC/IO.hs b/libraries/base/GHC/IO.hs index 63b47ff..118ebea 100644 --- a/libraries/base/GHC/IO.hs +++ b/libraries/base/GHC/IO.hs @@ -335,7 +335,7 @@ onException io what = io `catchException` \e -> do _ <- what -- use @mask_ $ forkIO ... at . This is particularly useful if you need -- to establish an exception handler in the forked thread before any -- asynchronous exceptions are received. To create a a new thread in --- an unmasked state use 'Control.Concurrent.forkIOUnmasked'. +-- an unmasked state use 'Control.Concurrent.forkIOWithUnmask'. -- mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b From git at git.haskell.org Sun May 7 19:38:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 19:38:17 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Libdw: Reduce maximum backtrace depth (20f6a4d) Message-ID: <20170507193817.1DBA33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/20f6a4de5d96b3bc0068d69103e4d57183226f35/ghc >--------------------------------------------------------------- commit 20f6a4de5d96b3bc0068d69103e4d57183226f35 Author: Ben Gamari Date: Mon Nov 21 21:50:55 2016 -0500 Libdw: Reduce maximum backtrace depth >--------------------------------------------------------------- 20f6a4de5d96b3bc0068d69103e4d57183226f35 rts/Libdw.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/Libdw.c b/rts/Libdw.c index 33a40a1..1e4f50e 100644 --- a/rts/Libdw.c +++ b/rts/Libdw.c @@ -16,7 +16,7 @@ #include #include -const int max_backtrace_depth = 5000; +const int max_backtrace_depth = 500; static BacktraceChunk *backtraceAllocChunk(BacktraceChunk *next) { BacktraceChunk *chunk = stgMallocBytes(sizeof(BacktraceChunk), From git at git.haskell.org Sun May 7 19:38:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 19:38:19 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: libdw: testsuite infrastructure (4d787a7) Message-ID: <20170507193819.C831B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/4d787a72296cc4d2c4985a266f09bba6e4477580/ghc >--------------------------------------------------------------- commit 4d787a72296cc4d2c4985a266f09bba6e4477580 Author: Ben Gamari Date: Tue Sep 1 22:51:55 2015 +0200 libdw: testsuite infrastructure >--------------------------------------------------------------- 4d787a72296cc4d2c4985a266f09bba6e4477580 testsuite/config/ghc | 4 ++++ testsuite/driver/testlib.py | 3 +++ 2 files changed, 7 insertions(+) diff --git a/testsuite/config/ghc b/testsuite/config/ghc index 6296394..102ae7d 100644 --- a/testsuite/config/ghc +++ b/testsuite/config/ghc @@ -13,6 +13,8 @@ config.hpc = 'hpc' config.gs = 'gs' config.confdir = '.' +config.libs_have_debug_info = libs_have_debug_info + # By default, the 'normal' and 'hpc' ways are enabled. In addition, certain # ways are enabled automatically if this GHC supports them. Ways that fall in # this group are 'optasm', 'optllvm', 'profasm', 'threaded1', 'threaded2', @@ -184,6 +186,8 @@ def get_compiler_info(): except: config.package_conf_cache_file = '' + config.rts_with_libdw = compilerInfoDict["RTS expects libdw"] == "YES" + # See Note [WayFlags] if config.ghc_dynamic: config.ghc_th_way_flags = "-dynamic" diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 1f08f5b..ec0fc54 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -407,6 +407,9 @@ def unregisterised( ): def compiler_profiled( ): return config.compiler_profiled +def rts_with_libdw( ): + return config.rts_with_libdw + def compiler_debugged( ): return config.compiler_debugged From git at git.haskell.org Sun May 7 19:38:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 19:38:22 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Add infrastructure for a simple statistical profiler (f9cb7a2) Message-ID: <20170507193822.955D53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/f9cb7a248c5049cc25344917a012b35d171f5999/ghc >--------------------------------------------------------------- commit f9cb7a248c5049cc25344917a012b35d171f5999 Author: Ben Gamari Date: Fri Sep 25 18:32:05 2015 +0200 Add infrastructure for a simple statistical profiler >--------------------------------------------------------------- f9cb7a248c5049cc25344917a012b35d171f5999 includes/rts/Config.h | 16 +++--- includes/rts/EventLogFormat.h | 4 +- rts/Trace.c | 13 +++++ rts/Trace.h | 12 +++++ rts/eventlog/EventLog.c | 118 ++++++++++++++++++++++++++++++++++++++++++ rts/eventlog/EventLog.h | 7 +++ 6 files changed, 163 insertions(+), 7 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 f9cb7a248c5049cc25344917a012b35d171f5999 From git at git.haskell.org Sun May 7 19:38:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 19:38:26 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Add test for DWARF unwinding through C stack (6f777c2) Message-ID: <20170507193826.1B0823A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/6f777c2652cf313530e465a8dca91518b348b791/ghc >--------------------------------------------------------------- commit 6f777c2652cf313530e465a8dca91518b348b791 Author: Ben Gamari Date: Fri Oct 23 11:37:36 2015 +0200 Add test for DWARF unwinding through C stack >--------------------------------------------------------------- 6f777c2652cf313530e465a8dca91518b348b791 .../tests/codeGen/should_run/DwarfUnwindToC.hs | 21 +++++++++ .../tests/codeGen/should_run/DwarfUnwindToC.stdout | 52 ++++++++++++++++++++++ testsuite/tests/codeGen/should_run/all.T | 1 + 3 files changed, 74 insertions(+) diff --git a/testsuite/tests/codeGen/should_run/DwarfUnwindToC.hs b/testsuite/tests/codeGen/should_run/DwarfUnwindToC.hs new file mode 100644 index 0000000..52db325 --- /dev/null +++ b/testsuite/tests/codeGen/should_run/DwarfUnwindToC.hs @@ -0,0 +1,21 @@ +import GHC.ExecutionStack + +-- | Trim object file names +cleanUpBacktrace :: String -> String +cleanUpBacktrace = unlines . map trimLine . lines + where + trimLine (' ':'i':'n':' ':_) = "" + trimLine (x:xs) = x : trimLine xs + trimLine [] = [] + +test :: Int -> IO () +test 0 = return () +test i = do + print i + showStackTrace >>= putStrLn . cleanUpBacktrace + test (i-1) + return () + +main = do + test 3 + print "Hello" diff --git a/testsuite/tests/codeGen/should_run/DwarfUnwindToC.stdout b/testsuite/tests/codeGen/should_run/DwarfUnwindToC.stdout new file mode 100644 index 0000000..11c0967 --- /dev/null +++ b/testsuite/tests/codeGen/should_run/DwarfUnwindToC.stdout @@ -0,0 +1,52 @@ +3 +Stack trace: + set_initial_registers (rts/Libdw.c:278.0) + dwfl_thread_getframes + + dwfl_getthreads + dwfl_getthread_frames + libdw_get_backtrace (rts/Libdw.c:249.0) + base_GHCziExecutionStackziInternal_collectStackTrace1_info (libraries/base/GHC/ExecutionStack/Internal.hsc:194.1) + base_GHCziExecutionStack_showStackTrace1_info (libraries/base/GHC/ExecutionStack.hs:47.1) + base_GHCziBase_bindIO1_info (libraries/base/GHC/Base.hs:1081.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + stg_catch_frame_info (rts/Exception.cmm:370.1) + stg_stop_thread_info (rts/StgStartup.cmm:42.1) + +2 +Stack trace: + set_initial_registers (rts/Libdw.c:278.0) + dwfl_thread_getframes + + dwfl_getthreads + dwfl_getthread_frames + libdw_get_backtrace (rts/Libdw.c:249.0) + base_GHCziExecutionStackziInternal_collectStackTrace1_info (libraries/base/GHC/ExecutionStack/Internal.hsc:194.1) + base_GHCziExecutionStack_showStackTrace1_info (libraries/base/GHC/ExecutionStack.hs:47.1) + base_GHCziBase_bindIO1_info (libraries/base/GHC/Base.hs:1081.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + stg_catch_frame_info (rts/Exception.cmm:370.1) + stg_stop_thread_info (rts/StgStartup.cmm:42.1) + +1 +Stack trace: + set_initial_registers (rts/Libdw.c:278.0) + dwfl_thread_getframes + + dwfl_getthreads + dwfl_getthread_frames + libdw_get_backtrace (rts/Libdw.c:249.0) + base_GHCziExecutionStackziInternal_collectStackTrace1_info (libraries/base/GHC/ExecutionStack/Internal.hsc:194.1) + base_GHCziExecutionStack_showStackTrace1_info (libraries/base/GHC/ExecutionStack.hs:47.1) + base_GHCziBase_bindIO1_info (libraries/base/GHC/Base.hs:1081.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + base_GHCziBase_thenIO1_info (libraries/base/GHC/Base.hs:1084.1) + stg_catch_frame_info (rts/Exception.cmm:370.1) + stg_stop_thread_info (rts/StgStartup.cmm:42.1) + +"Hello" diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 6318341..7f66f08 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -158,3 +158,4 @@ test('T9577', [ unless(arch('x86_64') or arch('i386'),skip), test('T13425', normal, compile_and_run, ['-O']) test('castFloatWord', normal, compile_and_run, ['-dcmm-lint']) +test('DwarfUnwindToC', [when(not rts_with_libdw() or not libs_have_debug_info(), skip)], compile_and_run, ['']) From git at git.haskell.org Sun May 7 19:38:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 19:38:28 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: users-guide: Document statistical profiler eventlog records (482ebdd) Message-ID: <20170507193828.EC9543A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/482ebdd2a2066e83aa5cd9df3b4164ce76ed44fc/ghc >--------------------------------------------------------------- commit 482ebdd2a2066e83aa5cd9df3b4164ce76ed44fc Author: Ben Gamari Date: Tue Dec 6 11:04:40 2016 -0500 users-guide: Document statistical profiler eventlog records >--------------------------------------------------------------- 482ebdd2a2066e83aa5cd9df3b4164ce76ed44fc docs/users_guide/eventlog-formats.rst | 35 +++++++++++++++++++++++++++++++++++ 1 file changed, 35 insertions(+) diff --git a/docs/users_guide/eventlog-formats.rst b/docs/users_guide/eventlog-formats.rst index 8d53f92..b826ad6 100644 --- a/docs/users_guide/eventlog-formats.rst +++ b/docs/users_guide/eventlog-formats.rst @@ -103,3 +103,38 @@ A variable-length event encoding a heap sample broken down by, * ``Word8``: Profile ID * ``Word64``: heap residency in bytes * ``String``: type or closure description, or module name + + +.. _statistical-profiler-formats: + +Statistical profiler formats +---------------------------- + +Samples +~~~~~~~ + +A block of samples from statistical profiling. A sample consists of a sample +value (e.g. an instruction pointer address) and a weight (e.g. how many times +the sample pointer was seen). + + * ``EVENT_STAT_PROF_SAMPLES`` (variable length) + * ``Word8``: Capability number + * ``Word8``: Sample trigger type + * ``Word8``: Sample value type + * Encoded samples + +The samples themselves are represented with a compressed encoding. Each sample +is represented by, + + * ``Word8``: Sample and weight encoding type + * top 4-bits: Sample encoding type + * ``0x0``: 8-bit positive offset to previous address + * ``0x1``: 8-bit negative offset to previous address + * ``0x4``: 32-bit positive offset to previous address + * ``0x5``: 32-bit negative offset to previous address + * ``0xf``: direct encoding + * bottom 4-bits: weight encoding type + * ``0``: ``weight == 1`` + * ``1``: weight encoded as ``Word8`` + * ``2``: weight encoded as ``Word16`` + * ``4``: weight encoded as ``Word32`` From git at git.haskell.org Sun May 7 19:38:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 19:38:31 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: testsuite: Add config.libs_have_debug_info (580f074) Message-ID: <20170507193831.B45103A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/580f074dd06d23d55c79b6c1c827ed2085509f98/ghc >--------------------------------------------------------------- commit 580f074dd06d23d55c79b6c1c827ed2085509f98 Author: Ben Gamari Date: Sun Oct 25 19:13:53 2015 +0100 testsuite: Add config.libs_have_debug_info It's not entirely clear that this is the right way to do this since the compiler we are testing may not have the same configuration as the current tree. We could add a "Libraries have debugging information" entry to `ghc --info` but this seems rather heavy just for the testsuite. >--------------------------------------------------------------- 580f074dd06d23d55c79b6c1c827ed2085509f98 testsuite/driver/testlib.py | 3 +++ testsuite/mk/test.mk | 6 ++++++ 2 files changed, 9 insertions(+) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index ec0fc54..93a8f6e 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -410,6 +410,9 @@ def compiler_profiled( ): def rts_with_libdw( ): return config.rts_with_libdw +def libs_have_debug_info( ): + return config.libs_have_debug_info + def compiler_debugged( ): return config.compiler_debugged diff --git a/testsuite/mk/test.mk b/testsuite/mk/test.mk index a44e200..391883f 100644 --- a/testsuite/mk/test.mk +++ b/testsuite/mk/test.mk @@ -77,6 +77,12 @@ RUNTEST_OPTS += -e ghc_compiler_always_flags="'$(TEST_HC_OPTS)'" RUNTEST_OPTS += -e config.compiler_debugged=$(GhcDebugged) +ifeq "$(filter -g, $(GhcLibHcOps))" "-g" +RUNTEST_OPTS += -e libs_have_debug_info=1 +else +RUNTEST_OPTS += -e libs_have_debug_info=0 +endif + ifeq "$(GhcWithNativeCodeGen)" "YES" RUNTEST_OPTS += -e ghc_with_native_codegen=1 else From git at git.haskell.org Sun May 7 19:38:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 19:38:34 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: HACK: Disable substitution checks (2c2c5b0) Message-ID: <20170507193834.84BD63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/2c2c5b0a2b75dccd9322e39c6dc02919cc645ce0/ghc >--------------------------------------------------------------- commit 2c2c5b0a2b75dccd9322e39c6dc02919cc645ce0 Author: Ben Gamari Date: Mon Nov 21 23:08:40 2016 -0500 HACK: Disable substitution checks >--------------------------------------------------------------- 2c2c5b0a2b75dccd9322e39c6dc02919cc645ce0 compiler/types/TyCoRep.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index 300ef80..cf757a9 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -2085,6 +2085,8 @@ isValidTCvSubst (TCvSubst in_scope tenv cenv) = -- Note [The substitution invariant]. checkValidSubst :: HasCallStack => TCvSubst -> [Type] -> [Coercion] -> a -> a checkValidSubst subst@(TCvSubst in_scope tenv cenv) tys cos a + | otherwise = a + | otherwise = ASSERT2( isValidTCvSubst subst, text "in_scope" <+> ppr in_scope $$ text "tenv" <+> ppr tenv $$ From git at git.haskell.org Sun May 7 19:38:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 19:38:37 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: StatProfile: Heap and blackhole sampling (a271068) Message-ID: <20170507193837.B6BDD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/a2710682c3fe30ed2c78bc2ade2bb692fcc79023/ghc >--------------------------------------------------------------- commit a2710682c3fe30ed2c78bc2ade2bb692fcc79023 Author: Ben Gamari Date: Sat May 6 20:58:12 2017 -0400 StatProfile: Heap and blackhole sampling Based on Peter Wortmann's c01384a26d7c9d22d26a760470bdb6379a2913ee. Lacking a better idea, I follow Peter's lead and hackily lay claim to R9 for funneling the attribution address to stg_gc_noregs. In addition I add support for profiling of blackhole wait events. >--------------------------------------------------------------- a2710682c3fe30ed2c78bc2ade2bb692fcc79023 includes/rts/Config.h | 5 +++ rts/Capability.c | 20 ++++++++++++ rts/Capability.h | 9 ++++++ rts/HeapStackCheck.cmm | 74 +++++++++++++++++++++++++++++++++++++++++++ rts/Schedule.c | 3 ++ rts/StatProfile.h | 63 ++++++++++++++++++++++++++++++++++++ rts/Trace.h | 2 ++ utils/deriveConstants/Main.hs | 4 +++ 8 files changed, 180 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 a2710682c3fe30ed2c78bc2ade2bb692fcc79023 From git at git.haskell.org Sun May 7 19:38:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 19:38:43 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Temporarily commit dwarf flavour (9c5fc8e) Message-ID: <20170507193843.D22053A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/9c5fc8ee592bfcc937a4a49d07f398874a360964/ghc >--------------------------------------------------------------- commit 9c5fc8ee592bfcc937a4a49d07f398874a360964 Author: Ben Gamari Date: Sun Jul 24 18:01:09 2016 +0200 Temporarily commit dwarf flavour >--------------------------------------------------------------- 9c5fc8ee592bfcc937a4a49d07f398874a360964 mk/flavours/dwarf.mk | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/mk/flavours/dwarf.mk b/mk/flavours/dwarf.mk new file mode 100644 index 0000000..6fd9cc7 --- /dev/null +++ b/mk/flavours/dwarf.mk @@ -0,0 +1,8 @@ +GhcStage1HcOpts += -DDEBUG +GhcStage2HcOpts += -DDEBUG +#GhcStage2HcOpts += -ddump-to-file -ddump-asm -ddump-cmm -dppr-debug +GhcLibHcOpts += -g +GhcLibHcOpts += -ddump-to-file -ddump-asm -ddump-cmm -ddump-debug -dppr-debug +GhcRtsHcOpts += -g +BUILD_PROF_LIBS = NO +DYNAMIC_GHC_PROGRAMS = NO From git at git.haskell.org Sun May 7 19:38:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 19:38:40 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Never tick primitive string literals (0e8370b) Message-ID: <20170507193840.996143A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/0e8370b0022859d020ec7b117a57ad3f9713f8c7/ghc >--------------------------------------------------------------- commit 0e8370b0022859d020ec7b117a57ad3f9713f8c7 Author: Ben Gamari Date: Sun Mar 19 11:53:01 2017 -0400 Never tick primitive string literals This is a more aggressive approach to the problem initially solved in f5b275a239d2554c4da0b7621211642bf3b10650, where top-level primitive string literals were being wrapped by ticks. This breaks the Core invariant descirbed in Note [CoreSyn top-level string literals]. However, the previous approach was incomplete and left several places where inappropriate ticks could sneak in. This commit kills the problem at the source: we simply never tick any primitive string literal expression. The assumption here is that these expressions are destined for the top-level, where they cannot be ticked, anyways. So even if they haven't been floated out yet there is no reason to tick them. This partially reverts commit f5b275a239d2554c4da0b7621211642bf3b10650. Test Plan: Validate with `-g` Reviewers: austin, scpmw, simonpj, simonmar, dfeuer Subscribers: dfeuer, simonmar, thomie Differential Revision: https://phabricator.haskell.org/D3063 >--------------------------------------------------------------- 0e8370b0022859d020ec7b117a57ad3f9713f8c7 compiler/coreSyn/CoreSyn.hs | 2 ++ compiler/coreSyn/CoreUtils.hs | 5 +++++ compiler/simplCore/FloatOut.hs | 33 +++++++++++++-------------------- compiler/simplCore/Simplify.hs | 10 ++-------- 4 files changed, 22 insertions(+), 28 deletions(-) diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs index a669437..f15433f 100644 --- a/compiler/coreSyn/CoreSyn.hs +++ b/compiler/coreSyn/CoreSyn.hs @@ -402,6 +402,8 @@ It is important to note that top-level primitive string literals cannot be wrapped in Ticks, as is otherwise done with lifted bindings. CoreToStg expects to see just a plain (Lit (MachStr ...)) expression on the RHS of primitive string bindings; anything else and things break. CoreLint checks this invariant. +To ensure that ticks don't sneak in CoreUtils.mkTick refuses to wrap any +primitve string expression with a tick. Also see Note [Compilation plan for top-level string literals]. diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index cc2d172..52fc2d1 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -299,6 +299,11 @@ mkTick t orig_expr = mkTick' id id orig_expr -> CoreExpr mkTick' top rest expr = case expr of + -- Never tick primitive string literals. These should ultimately float up to + -- the top-level where they must be unadorned. See Note + -- [CoreSyn top-level string literals] for details. + _ | exprIsLiteralString expr -> expr + -- Cost centre ticks should never be reordered relative to each -- other. Therefore we can stop whenever two collide. Tick t2 e diff --git a/compiler/simplCore/FloatOut.hs b/compiler/simplCore/FloatOut.hs index 72fc0d1..17ffba4 100644 --- a/compiler/simplCore/FloatOut.hs +++ b/compiler/simplCore/FloatOut.hs @@ -21,7 +21,7 @@ import DynFlags import ErrUtils ( dumpIfSet_dyn ) import Id ( Id, idArity, idType, isBottomingId, isJoinId, isJoinId_maybe ) -import BasicTypes ( TopLevelFlag(..), isTopLevel ) +import Var ( Var ) import SetLevels import UniqSupply ( UniqSupply ) import Bag @@ -735,26 +735,19 @@ atJoinCeiling (fs, floats, expr') wrapTick :: Tickish Id -> FloatBinds -> FloatBinds wrapTick t (FB tops ceils defns) - = FB (mapBag (wrap_bind TopLevel) tops) - (wrap_defns NotTopLevel ceils) - (M.map (M.map (wrap_defns NotTopLevel)) defns) + = FB (mapBag wrap_bind tops) (wrap_defns ceils) + (M.map (M.map wrap_defns) defns) where - wrap_defns toplvl = mapBag (wrap_one toplvl) - - wrap_bind toplvl (NonRec binder rhs) = NonRec binder (maybe_tick toplvl rhs) - wrap_bind toplvl (Rec pairs) = Rec (mapSnd (maybe_tick toplvl) pairs) - - wrap_one toplvl (FloatLet bind) = FloatLet (wrap_bind toplvl bind) - wrap_one toplvl (FloatCase e b c bs) = FloatCase (maybe_tick toplvl e) b c bs - - maybe_tick :: TopLevelFlag -> CoreExpr -> CoreExpr - maybe_tick toplvl e - -- We must take care not to tick top-level literal - -- strings as this violated the Core invariants. See Note [CoreSyn - -- top-level string literals]. - | isTopLevel toplvl && exprIsLiteralString e = e - | exprIsHNF e = tickHNFArgs t e - | otherwise = mkTick t e + wrap_defns = mapBag wrap_one + + wrap_bind (NonRec binder rhs) = NonRec binder (maybe_tick rhs) + wrap_bind (Rec pairs) = Rec (mapSnd maybe_tick pairs) + + wrap_one (FloatLet bind) = FloatLet (wrap_bind bind) + wrap_one (FloatCase e b c bs) = FloatCase (maybe_tick e) b c bs + + maybe_tick e | exprIsHNF e = tickHNFArgs t e + | otherwise = mkTick t e -- we don't need to wrap a tick around an HNF when we float it -- outside a tick: that is an invariant of the tick semantics -- Conversely, inlining of HNFs inside an SCC is allowed, and diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index 1c5534f..f445a19 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -611,17 +611,11 @@ prepareRhs top_lvl env0 id rhs0 -- On the other hand, for scoping ticks we need to be able to -- copy them on the floats, which in turn is only allowed if -- we can obtain non-counting ticks. - | (not (tickishCounts t) || tickishCanSplit t) + | not (tickishCounts t) || tickishCanSplit t = do { (is_exp, env', rhs') <- go n_val_args (zapFloats env) rhs -- env' has the extra let-bindings from -- the makeTrivial calls in 'go'; no join floats - ; let tickIt (id, expr) - -- we have to take care not to tick top-level literal - -- strings. See Note [CoreSyn top-level string literals]. - | isTopLevel top_lvl && exprIsLiteralString expr - = (id, expr) - | otherwise - = (id, mkTick (mkNoCount t) expr) + ; let tickIt (id, expr) = (id, mkTick (mkNoCount t) expr) floats' = seLetFloats env `addFlts` mapFloats (seLetFloats env') tickIt ; return (is_exp, env' { seLetFloats = floats' }, Tick t rhs') } From git at git.haskell.org Sun May 7 19:38:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 19:38:46 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: StatProf: Add RTS flags to enable particular samplers (97ccb91) Message-ID: <20170507193846.8E5F03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/97ccb918561ded9f813ca86ecf40871644c9ccd3/ghc >--------------------------------------------------------------- commit 97ccb918561ded9f813ca86ecf40871644c9ccd3 Author: Ben Gamari Date: Sun Nov 15 12:51:35 2015 +0100 StatProf: Add RTS flags to enable particular samplers >--------------------------------------------------------------- 97ccb918561ded9f813ca86ecf40871644c9ccd3 includes/rts/Flags.h | 24 +++++++++++++++--------- rts/RtsFlags.c | 50 ++++++++++++++++++++++++++++++++++++++++++++++++-- rts/StatProfile.h | 2 ++ 3 files changed, 65 insertions(+), 11 deletions(-) diff --git a/includes/rts/Flags.h b/includes/rts/Flags.h index 6700f9d..3ae0f94 100644 --- a/includes/rts/Flags.h +++ b/includes/rts/Flags.h @@ -155,6 +155,11 @@ typedef struct _PROFILING_FLAGS { } PROFILING_FLAGS; +typedef struct _STAT_PROFILE_FLAGS { + bool heapCheckSampling; + bool blackholeSampling; +} STAT_PROFILE_FLAGS; + #define TRACE_NONE 0 #define TRACE_EVENTLOG 1 #define TRACE_STDERR 2 @@ -234,15 +239,16 @@ typedef struct _TICKY_FLAGS { /* See Note [Synchronization of flags and base APIs] */ typedef struct _RTS_FLAGS { /* The first portion of RTS_FLAGS is invariant. */ - GC_FLAGS GcFlags; - CONCURRENT_FLAGS ConcFlags; - MISC_FLAGS MiscFlags; - DEBUG_FLAGS DebugFlags; - COST_CENTRE_FLAGS CcFlags; - PROFILING_FLAGS ProfFlags; - TRACE_FLAGS TraceFlags; - TICKY_FLAGS TickyFlags; - PAR_FLAGS ParFlags; + GC_FLAGS GcFlags; + CONCURRENT_FLAGS ConcFlags; + MISC_FLAGS MiscFlags; + DEBUG_FLAGS DebugFlags; + COST_CENTRE_FLAGS CcFlags; + PROFILING_FLAGS ProfFlags; + STAT_PROFILE_FLAGS StatProfileFlags; + TRACE_FLAGS TraceFlags; + TICKY_FLAGS TickyFlags; + PAR_FLAGS ParFlags; } RTS_FLAGS; #if defined(COMPILING_RTS_MAIN) diff --git a/rts/RtsFlags.c b/rts/RtsFlags.c index b51d644..e1cf8ea 100644 --- a/rts/RtsFlags.c +++ b/rts/RtsFlags.c @@ -106,6 +106,7 @@ static bool read_heap_profiling_flag(const char *arg); #endif #if defined(TRACING) +static bool read_stat_profiler_flag(const char *arg); static void read_trace_flags(const char *arg); #endif @@ -203,6 +204,11 @@ void initRtsFlagsDefaults(void) RtsFlags.ProfFlags.bioSelector = NULL; #endif +#if defined(STAT_PROFILE) + RtsFlags.StatProfileFlags.blackholeSampling = false; + RtsFlags.StatProfileFlags.heapCheckSampling = false; +#endif + #if defined(TRACING) RtsFlags.TraceFlags.tracing = TRACE_NONE; RtsFlags.TraceFlags.timestamp = false; @@ -306,6 +312,15 @@ usage_text[] = { " -P More detailed Time/Allocation profile in tree format", " -Pa Give information about *all* cost centres in tree format", " -pj Output cost-center profile in JSON format", +#if defined(STAT_PROFILE) +"", +" -pS" +" Enable recording of statistical profiler samples from", +" the given sample source. May be given multiple times.", +" The valid samplers are,", +" h = heap check (indicative of heap allocations)", +" b = black hole blocking (indicative of poor parallelism)", +#endif "", " -h Heap residency profile (hp2ps) (output file .hp)", " break-down: c = cost centre stack (default)", @@ -1058,8 +1073,21 @@ error = true; case 'P': /* detailed cost centre profiling (time/alloc) */ case 'p': /* cost centre profiling (time/alloc) */ OPTION_SAFE; - PROFILING_BUILD_ONLY( switch (rts_argv[arg][2]) { + case 's': +#if defined(TRACING) + error = read_stat_profiler_flag(rts_argv[arg]); +#else + errorBelch( + "statistical profiling flag %s given but program was" + " not built with tracing. Build with -eventlog to use" + " statistical profiling.", + rts_argv[arg]); + error = true; +#endif + break; + + PROFILING_BUILD_ONLY( case 'a': RtsFlags.CcFlags.doCostCentres = COST_CENTRES_ALL; if (rts_argv[arg][3] != '\0') { @@ -1079,11 +1107,12 @@ error = true; RtsFlags.CcFlags.doCostCentres = COST_CENTRES_SUMMARY; } break; + ) default: unchecked_arg_start++; goto check_rest; } - ) break; + break; case 'R': OPTION_SAFE; @@ -1819,6 +1848,23 @@ static bool read_heap_profiling_flag(const char *arg) #endif #if defined(TRACING) +// Returns whether the parse resulted in an error. +static bool read_stat_profiler_flag(const char *arg) +{ + switch (arg[2]) { + case 'h': + RtsFlags.StatProfileFlags.heapCheckSampling = true; + break; + case 'b': + RtsFlags.StatProfileFlags.blackholeSampling = true; + break; + default: + errorBelch("Unknown statistical profiler sampler flag %s", arg); + return true; + } + return false; +} + static void read_trace_flags(const char *arg) { const char *c; diff --git a/rts/StatProfile.h b/rts/StatProfile.h index 4a44cbb..8540c06 100644 --- a/rts/StatProfile.h +++ b/rts/StatProfile.h @@ -19,6 +19,7 @@ INLINE_HEADER void statProfileDumpHeapSamples(Capability *cap) { // See Note [Statistical profiling of heap allocations] + if (!RtsFlags.StatProfileFlags.heapCheckSampling) return; if (cap->heap_sample_count) { traceStatProfileSamples(cap, true, SAMPLE_BY_HEAP_ALLOC, SAMPLE_TYPE_INSTR_PTR, @@ -32,6 +33,7 @@ INLINE_HEADER void statProfileDumpBlackholeSamples(Capability *cap) { // See Note [Statistical profiling of black-hole allocations] + if (!RtsFlags.StatProfileFlags.blackholeSampling) return; if (cap->blackhole_sample_count) { traceStatProfileSamples(cap, true, SAMPLE_BY_BLACKHOLE, SAMPLE_TYPE_INSTR_PTR, From git at git.haskell.org Sun May 7 19:38:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 19:38:52 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: OptCoercion: Ensure that TyConApps match in arity (3d64db2) Message-ID: <20170507193852.E6FD53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/3d64db2064e52931623eb03519dbd64b743d3caa/ghc >--------------------------------------------------------------- commit 3d64db2064e52931623eb03519dbd64b743d3caa Author: Ben Gamari Date: Sun May 7 14:48:41 2017 -0400 OptCoercion: Ensure that TyConApps match in arity Previously we would >--------------------------------------------------------------- 3d64db2064e52931623eb03519dbd64b743d3caa compiler/types/OptCoercion.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/types/OptCoercion.hs b/compiler/types/OptCoercion.hs index b1aa646..03e1d6c 100644 --- a/compiler/types/OptCoercion.hs +++ b/compiler/types/OptCoercion.hs @@ -378,6 +378,7 @@ opt_univ env sym prov role oty1 oty2 | Just (tc1, tys1) <- splitTyConApp_maybe oty1 , Just (tc2, tys2) <- splitTyConApp_maybe oty2 , tc1 == tc2 + , equalLength tys1 tys2 -- NB: prov must not be the two interesting ones (ProofIrrel & Phantom); -- Phantom is already taken care of, and ProofIrrel doesn't relate tyconapps = let roles = tyConRolesX role tc1 From git at git.haskell.org Sun May 7 19:38:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 19:38:59 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Debugging output (1d62cee) Message-ID: <20170507193859.8EB383A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/1d62cee84f1c8300c79f8a867349b54cf032ecd3/ghc >--------------------------------------------------------------- commit 1d62cee84f1c8300c79f8a867349b54cf032ecd3 Author: Ben Gamari Date: Mon Nov 21 22:26:13 2016 -0500 Debugging output >--------------------------------------------------------------- 1d62cee84f1c8300c79f8a867349b54cf032ecd3 compiler/nativeGen/Dwarf.hs | 7 +++++++ compiler/nativeGen/Dwarf/Types.hs | 6 +++++- 2 files changed, 12 insertions(+), 1 deletion(-) diff --git a/compiler/nativeGen/Dwarf.hs b/compiler/nativeGen/Dwarf.hs index 1066169..497bb35 100644 --- a/compiler/nativeGen/Dwarf.hs +++ b/compiler/nativeGen/Dwarf.hs @@ -14,6 +14,8 @@ import Platform import Unique import UniqSupply +import ErrUtils + import Dwarf.Constants import Dwarf.Types @@ -89,6 +91,11 @@ dwarfGen df modLoc us blocks = do | otherwise = [DwarfARange lowLabel highLabel] let aranges = dwarfARangesSection $$ pprDwarfARanges aranges' unitU + let extractUnwinds blk = dblUnwind blk : foldMap extractUnwinds (dblBlocks blk) + dumpIfSet_dyn df Opt_D_dump_debug "Pre-dwarfGen" + (nest 4 $ vcat $ map (ppr . extractUnwinds) blocks) + dumpIfSet_dyn df Opt_D_dump_debug "Post-dwarfGen" + (nest 4 $ vcat $ foldMap (map ppr . extractUnwinds) procs) return (infoSct $$ abbrevSct $$ lineSct $$ frameSct $$ aranges, us'') -- | Build an address range entry for one proc. diff --git a/compiler/nativeGen/Dwarf/Types.hs b/compiler/nativeGen/Dwarf/Types.hs index d4d8e24..ebdbee3 100644 --- a/compiler/nativeGen/Dwarf/Types.hs +++ b/compiler/nativeGen/Dwarf/Types.hs @@ -264,6 +264,8 @@ data DwarfFrameProc , dwFdeBlocks :: [DwarfFrameBlock] -- ^ List of blocks. Order must match asm! } +instance Outputable DwarfFrameProc where + ppr x = ppr (dwFdeProc x) <> colon <+> hsep (map ppr $ dwFdeBlocks x) -- | Unwind instructions for a block. Will become part of the -- containing FDE. @@ -390,7 +392,9 @@ pprFrameBlock (DwarfFrameBlock hasInfo uws0) = if needsOffset then text "-1" else empty doc = sdocWithPlatform $ \plat -> pprByte dW_CFA_set_loc $$ pprWord lblDoc $$ - vcat (map (uncurry $ pprSetUnwind plat) changed) + vcat (map (uncurry $ pprSetUnwind' plat) changed) + pprSetUnwind' plat b c = + ifPprDebug (text "# "<+>ppr changed) $$ pprSetUnwind plat b c in (doc, uws) -- Note [Info Offset] From git at git.haskell.org Sun May 7 19:38:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 19:38:50 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Initial perf_event support (bb61d8d) Message-ID: <20170507193850.3ACB83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/bb61d8d11d8ae810d72ebdeff8c051678300bc95/ghc >--------------------------------------------------------------- commit bb61d8d11d8ae810d72ebdeff8c051678300bc95 Author: Ben Gamari Date: Sat Sep 26 20:32:52 2015 +0200 Initial perf_event support >--------------------------------------------------------------- bb61d8d11d8ae810d72ebdeff8c051678300bc95 configure.ac | 3 ++ distrib/configure.ac.in | 10 ++++ includes/rts/Config.h | 3 ++ mk/config.mk.in | 3 ++ rts/Capability.c | 10 ++++ rts/Capability.h | 5 ++ rts/PerfEvents.c | 127 ++++++++++++++++++++++++++++++++++++++++++++++++ rts/PerfEvents.h | 27 ++++++++++ rts/StatProfile.h | 39 ++++++++++++--- rts/Trace.h | 1 + 10 files changed, 220 insertions(+), 8 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 bb61d8d11d8ae810d72ebdeff8c051678300bc95 From git at git.haskell.org Sun May 7 19:38:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 19:38:56 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: rts: Emit debug information about program to event log (3db4bfb) Message-ID: <20170507193856.CE3D83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/3db4bfb98943ed2fc17dbab0bf5f1ff4c26b68e4/ghc >--------------------------------------------------------------- commit 3db4bfb98943ed2fc17dbab0bf5f1ff4c26b68e4 Author: Ben Gamari Date: Fri Sep 25 16:45:16 2015 +0200 rts: Emit debug information about program to event log This commit adds support to the RTS for traversing the debug information present in a program and emitting it to the event log for later consumption by debugging and performance analysis tools. This includes source note, symbol, and address range information derived from the DWARF annotations produced by GHC. Unfortunately one function necessary for traversing GHC's extended DWARF information, `dwarf_cu_getdwarf`, was only introduced in libdw 0.160. Consequently we won't be able to support statistical profiling in releases earlier than this. >--------------------------------------------------------------- 3db4bfb98943ed2fc17dbab0bf5f1ff4c26b68e4 configure.ac | 7 ++ includes/rts/EventLogFormat.h | 9 +- rts/LibdwScrape.c | 287 ++++++++++++++++++++++++++++++++++++++++++ rts/LibdwScrape.h | 12 ++ rts/RtsStartup.c | 2 + rts/Trace.c | 24 ++++ rts/Trace.h | 19 ++- rts/eventlog/EventLog.c | 77 ++++++++++++ rts/eventlog/EventLog.h | 18 +++ 9 files changed, 453 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 3db4bfb98943ed2fc17dbab0bf5f1ff4c26b68e4 From git at git.haskell.org Sun May 7 19:39:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 19:39:01 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof's head updated: OptCoercion: Ensure that TyConApps match in arity (3d64db2) Message-ID: <20170507193901.C19FC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/libdw-prof' now includes: 38a3819 Add regression tests for #12947, #13640 4a6cb5e Add testsuite/timeout/TimeMe to .gitignore ed0c7f8 Add regression test for #13651 baa18de testsuite: add new test for desugar warnings/errors with -fno-code 1840121 base: Fix documentation for forkIOWithUnmask 579749d Bump Cabal submodule to the 2.0.0.0 tag 9c5fc8e Temporarily commit dwarf flavour 2c2c5b0 HACK: Disable substitution checks 1d62cee Debugging output 20f6a4d Libdw: Reduce maximum backtrace depth 4d787a7 libdw: testsuite infrastructure 580f074 testsuite: Add config.libs_have_debug_info 6f777c2 Add test for DWARF unwinding through C stack 3db4bfb rts: Emit debug information about program to event log f9cb7a2 Add infrastructure for a simple statistical profiler a271068 StatProfile: Heap and blackhole sampling bb61d8d Initial perf_event support 97ccb91 StatProf: Add RTS flags to enable particular samplers 482ebdd users-guide: Document statistical profiler eventlog records 0e8370b Never tick primitive string literals 3d64db2 OptCoercion: Ensure that TyConApps match in arity From git at git.haskell.org Sun May 7 21:41:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 21:41:49 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: StatProf: Add RTS flags to enable particular samplers (37eb34d) Message-ID: <20170507214149.7073E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/37eb34d472626ee5f74545aa30f81e6ea65a4877/ghc >--------------------------------------------------------------- commit 37eb34d472626ee5f74545aa30f81e6ea65a4877 Author: Ben Gamari Date: Sun Nov 15 12:51:35 2015 +0100 StatProf: Add RTS flags to enable particular samplers >--------------------------------------------------------------- 37eb34d472626ee5f74545aa30f81e6ea65a4877 includes/rts/Flags.h | 24 +++++++++++++++--------- rts/RtsFlags.c | 52 ++++++++++++++++++++++++++++++++++++++++++++++++++-- rts/StatProfile.h | 2 ++ 3 files changed, 67 insertions(+), 11 deletions(-) diff --git a/includes/rts/Flags.h b/includes/rts/Flags.h index 6700f9d..3ae0f94 100644 --- a/includes/rts/Flags.h +++ b/includes/rts/Flags.h @@ -155,6 +155,11 @@ typedef struct _PROFILING_FLAGS { } PROFILING_FLAGS; +typedef struct _STAT_PROFILE_FLAGS { + bool heapCheckSampling; + bool blackholeSampling; +} STAT_PROFILE_FLAGS; + #define TRACE_NONE 0 #define TRACE_EVENTLOG 1 #define TRACE_STDERR 2 @@ -234,15 +239,16 @@ typedef struct _TICKY_FLAGS { /* See Note [Synchronization of flags and base APIs] */ typedef struct _RTS_FLAGS { /* The first portion of RTS_FLAGS is invariant. */ - GC_FLAGS GcFlags; - CONCURRENT_FLAGS ConcFlags; - MISC_FLAGS MiscFlags; - DEBUG_FLAGS DebugFlags; - COST_CENTRE_FLAGS CcFlags; - PROFILING_FLAGS ProfFlags; - TRACE_FLAGS TraceFlags; - TICKY_FLAGS TickyFlags; - PAR_FLAGS ParFlags; + GC_FLAGS GcFlags; + CONCURRENT_FLAGS ConcFlags; + MISC_FLAGS MiscFlags; + DEBUG_FLAGS DebugFlags; + COST_CENTRE_FLAGS CcFlags; + PROFILING_FLAGS ProfFlags; + STAT_PROFILE_FLAGS StatProfileFlags; + TRACE_FLAGS TraceFlags; + TICKY_FLAGS TickyFlags; + PAR_FLAGS ParFlags; } RTS_FLAGS; #if defined(COMPILING_RTS_MAIN) diff --git a/rts/RtsFlags.c b/rts/RtsFlags.c index b51d644..b5ae57f 100644 --- a/rts/RtsFlags.c +++ b/rts/RtsFlags.c @@ -106,6 +106,7 @@ static bool read_heap_profiling_flag(const char *arg); #endif #if defined(TRACING) +static bool read_stat_profiler_flag(const char *arg); static void read_trace_flags(const char *arg); #endif @@ -203,6 +204,11 @@ void initRtsFlagsDefaults(void) RtsFlags.ProfFlags.bioSelector = NULL; #endif +#if defined(STAT_PROFILE) + RtsFlags.StatProfileFlags.blackholeSampling = false; + RtsFlags.StatProfileFlags.heapCheckSampling = false; +#endif + #if defined(TRACING) RtsFlags.TraceFlags.tracing = TRACE_NONE; RtsFlags.TraceFlags.timestamp = false; @@ -306,6 +312,17 @@ usage_text[] = { " -P More detailed Time/Allocation profile in tree format", " -Pa Give information about *all* cost centres in tree format", " -pj Output cost-center profile in JSON format", +#endif +#if defined(STAT_PROFILE) +"", +" -pS", +" Enable recording of statistical profiler samples from", +" the given sample source. May be given multiple times.", +" The valid samplers are,", +" h = heap check (indicative of heap allocations)", +" b = black hole blocking (indicative of poor parallelism)", +#endif +#if defined(PROFILING) "", " -h Heap residency profile (hp2ps) (output file .hp)", " break-down: c = cost centre stack (default)", @@ -1058,8 +1075,21 @@ error = true; case 'P': /* detailed cost centre profiling (time/alloc) */ case 'p': /* cost centre profiling (time/alloc) */ OPTION_SAFE; - PROFILING_BUILD_ONLY( switch (rts_argv[arg][2]) { + case 'S': +#if defined(TRACING) + error = read_stat_profiler_flag(rts_argv[arg]); +#else + errorBelch( + "statistical profiling flag %s given but program was" + " not built with tracing. Build with -eventlog to use" + " statistical profiling.", + rts_argv[arg]); + error = true; +#endif + break; + + PROFILING_BUILD_ONLY( case 'a': RtsFlags.CcFlags.doCostCentres = COST_CENTRES_ALL; if (rts_argv[arg][3] != '\0') { @@ -1079,11 +1109,12 @@ error = true; RtsFlags.CcFlags.doCostCentres = COST_CENTRES_SUMMARY; } break; + ) default: unchecked_arg_start++; goto check_rest; } - ) break; + break; case 'R': OPTION_SAFE; @@ -1819,6 +1850,23 @@ static bool read_heap_profiling_flag(const char *arg) #endif #if defined(TRACING) +// Returns whether the parse resulted in an error. +static bool read_stat_profiler_flag(const char *arg) +{ + switch (arg[3]) { + case 'h': + RtsFlags.StatProfileFlags.heapCheckSampling = true; + break; + case 'b': + RtsFlags.StatProfileFlags.blackholeSampling = true; + break; + default: + errorBelch("Unknown statistical profiler sampler flag %s", arg); + return true; + } + return false; +} + static void read_trace_flags(const char *arg) { const char *c; diff --git a/rts/StatProfile.h b/rts/StatProfile.h index 4a44cbb..8540c06 100644 --- a/rts/StatProfile.h +++ b/rts/StatProfile.h @@ -19,6 +19,7 @@ INLINE_HEADER void statProfileDumpHeapSamples(Capability *cap) { // See Note [Statistical profiling of heap allocations] + if (!RtsFlags.StatProfileFlags.heapCheckSampling) return; if (cap->heap_sample_count) { traceStatProfileSamples(cap, true, SAMPLE_BY_HEAP_ALLOC, SAMPLE_TYPE_INSTR_PTR, @@ -32,6 +33,7 @@ INLINE_HEADER void statProfileDumpBlackholeSamples(Capability *cap) { // See Note [Statistical profiling of black-hole allocations] + if (!RtsFlags.StatProfileFlags.blackholeSampling) return; if (cap->blackhole_sample_count) { traceStatProfileSamples(cap, true, SAMPLE_BY_BLACKHOLE, SAMPLE_TYPE_INSTR_PTR, From git at git.haskell.org Sun May 7 21:41:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 21:41:52 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: users-guide: Document statistical profiler eventlog records (363af65) Message-ID: <20170507214152.3ECE33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/363af65dafc894065aeb63be18b2b15947702ea4/ghc >--------------------------------------------------------------- commit 363af65dafc894065aeb63be18b2b15947702ea4 Author: Ben Gamari Date: Tue Dec 6 11:04:40 2016 -0500 users-guide: Document statistical profiler eventlog records >--------------------------------------------------------------- 363af65dafc894065aeb63be18b2b15947702ea4 docs/users_guide/eventlog-formats.rst | 35 +++++++++++++++++++++++++++++++++++ 1 file changed, 35 insertions(+) diff --git a/docs/users_guide/eventlog-formats.rst b/docs/users_guide/eventlog-formats.rst index 8d53f92..b826ad6 100644 --- a/docs/users_guide/eventlog-formats.rst +++ b/docs/users_guide/eventlog-formats.rst @@ -103,3 +103,38 @@ A variable-length event encoding a heap sample broken down by, * ``Word8``: Profile ID * ``Word64``: heap residency in bytes * ``String``: type or closure description, or module name + + +.. _statistical-profiler-formats: + +Statistical profiler formats +---------------------------- + +Samples +~~~~~~~ + +A block of samples from statistical profiling. A sample consists of a sample +value (e.g. an instruction pointer address) and a weight (e.g. how many times +the sample pointer was seen). + + * ``EVENT_STAT_PROF_SAMPLES`` (variable length) + * ``Word8``: Capability number + * ``Word8``: Sample trigger type + * ``Word8``: Sample value type + * Encoded samples + +The samples themselves are represented with a compressed encoding. Each sample +is represented by, + + * ``Word8``: Sample and weight encoding type + * top 4-bits: Sample encoding type + * ``0x0``: 8-bit positive offset to previous address + * ``0x1``: 8-bit negative offset to previous address + * ``0x4``: 32-bit positive offset to previous address + * ``0x5``: 32-bit negative offset to previous address + * ``0xf``: direct encoding + * bottom 4-bits: weight encoding type + * ``0``: ``weight == 1`` + * ``1``: weight encoded as ``Word8`` + * ``2``: weight encoded as ``Word16`` + * ``4``: weight encoded as ``Word32`` From git at git.haskell.org Sun May 7 21:41:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 21:41:55 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: OptCoercion: Ensure that TyConApps match in arity (2d5c377) Message-ID: <20170507214155.094A03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/2d5c377569253f3468efc0577d07e1ef281e9d99/ghc >--------------------------------------------------------------- commit 2d5c377569253f3468efc0577d07e1ef281e9d99 Author: Ben Gamari Date: Sun May 7 14:48:41 2017 -0400 OptCoercion: Ensure that TyConApps match in arity Previously we would >--------------------------------------------------------------- 2d5c377569253f3468efc0577d07e1ef281e9d99 compiler/types/OptCoercion.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/types/OptCoercion.hs b/compiler/types/OptCoercion.hs index b1aa646..03e1d6c 100644 --- a/compiler/types/OptCoercion.hs +++ b/compiler/types/OptCoercion.hs @@ -378,6 +378,7 @@ opt_univ env sym prov role oty1 oty2 | Just (tc1, tys1) <- splitTyConApp_maybe oty1 , Just (tc2, tys2) <- splitTyConApp_maybe oty2 , tc1 == tc2 + , equalLength tys1 tys2 -- NB: prov must not be the two interesting ones (ProofIrrel & Phantom); -- Phantom is already taken care of, and ProofIrrel doesn't relate tyconapps = let roles = tyConRolesX role tc1 From git at git.haskell.org Sun May 7 21:41:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 May 2017 21:41:57 +0000 (UTC) Subject: [commit: ghc] wip/libdw-prof: Never tick primitive string literals (c3cc229) Message-ID: <20170507214157.BF0923A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/libdw-prof Link : http://ghc.haskell.org/trac/ghc/changeset/c3cc22924b3b1d144f877af1aafdd70aa5191f45/ghc >--------------------------------------------------------------- commit c3cc22924b3b1d144f877af1aafdd70aa5191f45 Author: Ben Gamari Date: Sun Mar 19 11:53:01 2017 -0400 Never tick primitive string literals This is a more aggressive approach to the problem initially solved in f5b275a239d2554c4da0b7621211642bf3b10650, where top-level primitive string literals were being wrapped by ticks. This breaks the Core invariant descirbed in Note [CoreSyn top-level string literals]. However, the previous approach was incomplete and left several places where inappropriate ticks could sneak in. This commit kills the problem at the source: we simply never tick any primitive string literal expression. The assumption here is that these expressions are destined for the top-level, where they cannot be ticked, anyways. So even if they haven't been floated out yet there is no reason to tick them. This partially reverts commit f5b275a239d2554c4da0b7621211642bf3b10650. Test Plan: Validate with `-g` Reviewers: austin, scpmw, simonpj, simonmar, dfeuer Subscribers: dfeuer, simonmar, thomie Differential Revision: https://phabricator.haskell.org/D3063 >--------------------------------------------------------------- c3cc22924b3b1d144f877af1aafdd70aa5191f45 compiler/coreSyn/CoreSyn.hs | 2 ++ compiler/coreSyn/CoreUtils.hs | 5 +++++ compiler/simplCore/FloatOut.hs | 33 +++++++++++++-------------------- compiler/simplCore/Simplify.hs | 10 ++-------- 4 files changed, 22 insertions(+), 28 deletions(-) diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs index a669437..f15433f 100644 --- a/compiler/coreSyn/CoreSyn.hs +++ b/compiler/coreSyn/CoreSyn.hs @@ -402,6 +402,8 @@ It is important to note that top-level primitive string literals cannot be wrapped in Ticks, as is otherwise done with lifted bindings. CoreToStg expects to see just a plain (Lit (MachStr ...)) expression on the RHS of primitive string bindings; anything else and things break. CoreLint checks this invariant. +To ensure that ticks don't sneak in CoreUtils.mkTick refuses to wrap any +primitve string expression with a tick. Also see Note [Compilation plan for top-level string literals]. diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index cc2d172..52fc2d1 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -299,6 +299,11 @@ mkTick t orig_expr = mkTick' id id orig_expr -> CoreExpr mkTick' top rest expr = case expr of + -- Never tick primitive string literals. These should ultimately float up to + -- the top-level where they must be unadorned. See Note + -- [CoreSyn top-level string literals] for details. + _ | exprIsLiteralString expr -> expr + -- Cost centre ticks should never be reordered relative to each -- other. Therefore we can stop whenever two collide. Tick t2 e diff --git a/compiler/simplCore/FloatOut.hs b/compiler/simplCore/FloatOut.hs index 72fc0d1..17ffba4 100644 --- a/compiler/simplCore/FloatOut.hs +++ b/compiler/simplCore/FloatOut.hs @@ -21,7 +21,7 @@ import DynFlags import ErrUtils ( dumpIfSet_dyn ) import Id ( Id, idArity, idType, isBottomingId, isJoinId, isJoinId_maybe ) -import BasicTypes ( TopLevelFlag(..), isTopLevel ) +import Var ( Var ) import SetLevels import UniqSupply ( UniqSupply ) import Bag @@ -735,26 +735,19 @@ atJoinCeiling (fs, floats, expr') wrapTick :: Tickish Id -> FloatBinds -> FloatBinds wrapTick t (FB tops ceils defns) - = FB (mapBag (wrap_bind TopLevel) tops) - (wrap_defns NotTopLevel ceils) - (M.map (M.map (wrap_defns NotTopLevel)) defns) + = FB (mapBag wrap_bind tops) (wrap_defns ceils) + (M.map (M.map wrap_defns) defns) where - wrap_defns toplvl = mapBag (wrap_one toplvl) - - wrap_bind toplvl (NonRec binder rhs) = NonRec binder (maybe_tick toplvl rhs) - wrap_bind toplvl (Rec pairs) = Rec (mapSnd (maybe_tick toplvl) pairs) - - wrap_one toplvl (FloatLet bind) = FloatLet (wrap_bind toplvl bind) - wrap_one toplvl (FloatCase e b c bs) = FloatCase (maybe_tick toplvl e) b c bs - - maybe_tick :: TopLevelFlag -> CoreExpr -> CoreExpr - maybe_tick toplvl e - -- We must take care not to tick top-level literal - -- strings as this violated the Core invariants. See Note [CoreSyn - -- top-level string literals]. - | isTopLevel toplvl && exprIsLiteralString e = e - | exprIsHNF e = tickHNFArgs t e - | otherwise = mkTick t e + wrap_defns = mapBag wrap_one + + wrap_bind (NonRec binder rhs) = NonRec binder (maybe_tick rhs) + wrap_bind (Rec pairs) = Rec (mapSnd maybe_tick pairs) + + wrap_one (FloatLet bind) = FloatLet (wrap_bind bind) + wrap_one (FloatCase e b c bs) = FloatCase (maybe_tick e) b c bs + + maybe_tick e | exprIsHNF e = tickHNFArgs t e + | otherwise = mkTick t e -- we don't need to wrap a tick around an HNF when we float it -- outside a tick: that is an invariant of the tick semantics -- Conversely, inlining of HNFs inside an SCC is allowed, and diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index 1c5534f..f445a19 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -611,17 +611,11 @@ prepareRhs top_lvl env0 id rhs0 -- On the other hand, for scoping ticks we need to be able to -- copy them on the floats, which in turn is only allowed if -- we can obtain non-counting ticks. - | (not (tickishCounts t) || tickishCanSplit t) + | not (tickishCounts t) || tickishCanSplit t = do { (is_exp, env', rhs') <- go n_val_args (zapFloats env) rhs -- env' has the extra let-bindings from -- the makeTrivial calls in 'go'; no join floats - ; let tickIt (id, expr) - -- we have to take care not to tick top-level literal - -- strings. See Note [CoreSyn top-level string literals]. - | isTopLevel top_lvl && exprIsLiteralString expr - = (id, expr) - | otherwise - = (id, mkTick (mkNoCount t) expr) + ; let tickIt (id, expr) = (id, mkTick (mkNoCount t) expr) floats' = seLetFloats env `addFlts` mapFloats (seLetFloats env') tickIt ; return (is_exp, env' { seLetFloats = floats' }, Tick t rhs') } From git at git.haskell.org Mon May 8 13:26:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 May 2017 13:26:34 +0000 (UTC) Subject: [commit: ghc] master: [Docs] Prefer cost centre (c685a44) Message-ID: <20170508132634.BC7B23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c685a44776ca77cad813f32e3cc7f7a42daf1d7d/ghc >--------------------------------------------------------------- commit c685a44776ca77cad813f32e3cc7f7a42daf1d7d Author: Bartosz Nitka Date: Mon May 8 06:26:12 2017 -0700 [Docs] Prefer cost centre There may be some subtlety I'm not seeing with the usage of center vs centre. Otherwise this makes it more consistent in the docs. There's one instance in 8.0.2-notes.rst, but I'm not sure if we want to modify it retroactively. Test Plan: harbormaster? Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: rwbarton, thomie, simonmar Differential Revision: https://phabricator.haskell.org/D3548 >--------------------------------------------------------------- c685a44776ca77cad813f32e3cc7f7a42daf1d7d docs/users_guide/8.0.2-notes.rst | 2 +- docs/users_guide/eventlog-formats.rst | 16 ++++++++-------- docs/users_guide/profiling.rst | 6 +++--- 3 files changed, 12 insertions(+), 12 deletions(-) diff --git a/docs/users_guide/8.0.2-notes.rst b/docs/users_guide/8.0.2-notes.rst index 237c3b9..7c2e2d7 100644 --- a/docs/users_guide/8.0.2-notes.rst +++ b/docs/users_guide/8.0.2-notes.rst @@ -171,7 +171,7 @@ Runtime system `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. +- Profiles from the cost-centre profiler now provide source span information. (see :ghc-ticket:`11543`). - The number of threads used for garbage collection is now configurable diff --git a/docs/users_guide/eventlog-formats.rst b/docs/users_guide/eventlog-formats.rst index 8d53f92..f7eb1ca 100644 --- a/docs/users_guide/eventlog-formats.rst +++ b/docs/users_guide/eventlog-formats.rst @@ -46,24 +46,24 @@ A single fixed-width event emitted during program start-up describing the sample * ``String``: Retainer filter * ``String``: Biography filter -Cost center definitions +Cost centre definitions ^^^^^^^^^^^^^^^^^^^^^^^ -A variable-length packet produced once for each cost center, +A variable-length packet produced once for each cost centre, * ``EVENT_HEAP_PROF_COST_CENTRE`` - * ``Word32``: cost center number + * ``Word32``: cost centre number * ``String``: label * ``String``: module * ``String``: source location * ``Word8``: flags - * bit 0: is the cost-center a CAF? + * bit 0: is the cost-centre a CAF? Sample event types ~~~~~~~~~~~~~~~~~~ -A sample (consisting of a list of break-down classes, e.g. cost centers, and +A sample (consisting of a list of break-down classes, e.g. cost centres, and heap residency sizes), is to be encoded in the body of one or more events. We mark the beginning of a new sample with an ``EVENT_HEAP_PROF_SAMPLE_BEGIN`` @@ -78,17 +78,17 @@ in length a single sample may need to be split among multiple determined by the break-down type. -Cost-center break-down +Cost-centre break-down ^^^^^^^^^^^^^^^^^^^^^^ A variable-length packet encoding a heap profile sample broken down by, - * cost-center (``-hc``) + * cost-centre (``-hc``) * ``EVENT_HEAP_PROF_SAMPLE_COST_CENTRE`` * ``Word8``: Profile ID * ``Word64``: heap residency in bytes * ``Word8``: stack depth - * ``Word32[]``: cost center stack starting with inner-most (cost center numbers) + * ``Word32[]``: cost centre stack starting with inner-most (cost centre numbers) String break-down diff --git a/docs/users_guide/profiling.rst b/docs/users_guide/profiling.rst index d035cc5..cf345ed 100644 --- a/docs/users_guide/profiling.rst +++ b/docs/users_guide/profiling.rst @@ -419,11 +419,11 @@ enclosed between ``+RTS ... -RTS`` as usual): .. rts-flag:: -po ⟨stem⟩ The :rts-flag:`-po` option overrides the stem used to form the output file - paths for the cost-center profiler (see :rts-flag:`-p` and :rts-flag:`-pj` + paths for the cost-centre profiler (see :rts-flag:`-p` and :rts-flag:`-pj` flags above) and heap profiler (see :rts-flag:`-h`). For instance, running a program with ``+RTS -h -p -pohello-world`` would - produce a heap profile named :file:`hello-world.hp` and a cost-center + produce a heap profile named :file:`hello-world.hp` and a cost-centre profile named :file:`hello-world.prof`. .. rts-flag:: -V @@ -490,7 +490,7 @@ tree-like object (which we'll call a "cost-centre stack" here) with the following properties, ``id`` (integral number) - The ``id`` of a cost-center listed in the ``cost_centres`` list. + The ``id`` of a cost-centre listed in the ``cost_centres`` list. ``entries`` (integral number) How many times was this cost-centre entered? ``ticks`` (integral number) From git at git.haskell.org Mon May 8 21:37:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 May 2017 21:37:27 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Fix a variety of warnings (476307c) Message-ID: <20170508213727.4E7353A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/476307cee7ff142b0eff91d45fddf17775417814/ghc >--------------------------------------------------------------- commit 476307cee7ff142b0eff91d45fddf17775417814 Author: Ben Gamari Date: Mon May 8 17:35:05 2017 -0400 users-guide: Fix a variety of warnings Including #13665. >--------------------------------------------------------------- 476307cee7ff142b0eff91d45fddf17775417814 docs/users_guide/8.2.1-notes.rst | 3 ++- docs/users_guide/8.4.1-notes.rst | 5 ++--- docs/users_guide/eventlog-formats.rst | 3 +++ docs/users_guide/glasgow_exts.rst | 2 +- docs/users_guide/using-optimisation.rst | 3 +-- docs/users_guide/using-warnings.rst | 2 ++ 6 files changed, 11 insertions(+), 7 deletions(-) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index 57c22a3..ba17e35 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -418,7 +418,8 @@ filepath ghc ~~~ -- +- Version number 8.2.1 + ghc-boot ~~~~~~~~ diff --git a/docs/users_guide/8.4.1-notes.rst b/docs/users_guide/8.4.1-notes.rst index 71eaa40..62173d5 100644 --- a/docs/users_guide/8.4.1-notes.rst +++ b/docs/users_guide/8.4.1-notes.rst @@ -76,9 +76,8 @@ Now we generate :: _ == _ = error ... -- Lots of other bugs. See `Trac - `_ - for a complete list. +- Lots of other bugs. See `Trac `_ + for a complete list. Runtime system ~~~~~~~~~~~~~~ diff --git a/docs/users_guide/eventlog-formats.rst b/docs/users_guide/eventlog-formats.rst index f7eb1ca..8b1427d 100644 --- a/docs/users_guide/eventlog-formats.rst +++ b/docs/users_guide/eventlog-formats.rst @@ -32,12 +32,14 @@ A single fixed-width event emitted during program start-up describing the sample * ``Word8``: Profile ID * ``Word64``: Sampling period in nanoseconds * ``Word32``: Sample break-down type. One of, + * ``SAMPLE_TYPE_COST_CENTER`` (output from ``-hc``) * ``SAMPLE_TYPE_CLOSURE_DESCR`` (output from ``-hd``) * ``SAMPLE_TYPE_RETAINER`` (output from ``-hr``) * ``SAMPLE_TYPE_MODULE`` (output from ``-hm``) * ``SAMPLE_TYPE_TYPE_DESCR`` (output from ``-hy``) * ``SAMPLE_TYPE_BIOGRAPHY`` (output from ``-hb``) + * ``String``: Module filter * ``String``: Closure description filter * ``String``: Type description filter @@ -57,6 +59,7 @@ A variable-length packet produced once for each cost centre, * ``String``: module * ``String``: source location * ``Word8``: flags + * bit 0: is the cost-centre a CAF? diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 6e394e7..2b7b652 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -10545,7 +10545,7 @@ for constructing pretty-printed error messages, :: | ErrorMessage :<>: ErrorMessage -- Put two chunks of error message next to each other | ErrorMessage :$$: ErrorMessage -- Put two chunks of error message above each other -in the ``GHC.TypeLits`` :base-ref:`module `. +in the ``GHC.TypeLits`` :base-ref:`module `. For instance, we might use this interface to provide a more useful error message for applications of ``show`` on unsaturated functions like this, :: diff --git a/docs/users_guide/using-optimisation.rst b/docs/users_guide/using-optimisation.rst index d52ed04..cfecc34 100644 --- a/docs/users_guide/using-optimisation.rst +++ b/docs/users_guide/using-optimisation.rst @@ -108,8 +108,7 @@ The easiest way to see what ``-O`` (etc.) “really mean” is to run with These flags turn on and off individual optimisations. Flags marked as on by default are enabled by ``-O``, and as such you shouldn't need to set any of them explicitly. A flag ``-fwombat`` can be negated -by saying ``-fno-wombat``. See :ref:`options-f-compact` for a compact -list. +by saying ``-fno-wombat``. .. ghc-flag:: -fcase-merge diff --git a/docs/users_guide/using-warnings.rst b/docs/users_guide/using-warnings.rst index 21594ec..ed2b12b 100644 --- a/docs/users_guide/using-warnings.rst +++ b/docs/users_guide/using-warnings.rst @@ -104,6 +104,7 @@ to abort. warnings when doing batch compilation. .. ghc-flag:: -Werror= + :noindex: :implies: ``-W`` @@ -116,6 +117,7 @@ to abort. default, but can be useful to negate a :ghc-flag:`-Werror` flag. .. ghc-flag:: -Wwarn= + :noindex: Causes a specific warning to be treated as normal warning, not fatal error. From git at git.haskell.org Mon May 8 21:39:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 May 2017 21:39:42 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: [Docs] Prefer cost centre (742b8f1) Message-ID: <20170508213942.1EC293A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/742b8f150f95cadd761a55c48a68ab0a6cab9e4d/ghc >--------------------------------------------------------------- commit 742b8f150f95cadd761a55c48a68ab0a6cab9e4d Author: Bartosz Nitka Date: Mon May 8 06:26:12 2017 -0700 [Docs] Prefer cost centre There may be some subtlety I'm not seeing with the usage of center vs centre. Otherwise this makes it more consistent in the docs. There's one instance in 8.0.2-notes.rst, but I'm not sure if we want to modify it retroactively. Test Plan: harbormaster? Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: rwbarton, thomie, simonmar Differential Revision: https://phabricator.haskell.org/D3548 (cherry picked from commit c685a44776ca77cad813f32e3cc7f7a42daf1d7d) >--------------------------------------------------------------- 742b8f150f95cadd761a55c48a68ab0a6cab9e4d docs/users_guide/8.0.2-notes.rst | 2 +- docs/users_guide/eventlog-formats.rst | 16 ++++++++-------- docs/users_guide/profiling.rst | 6 +++--- 3 files changed, 12 insertions(+), 12 deletions(-) diff --git a/docs/users_guide/8.0.2-notes.rst b/docs/users_guide/8.0.2-notes.rst index 237c3b9..7c2e2d7 100644 --- a/docs/users_guide/8.0.2-notes.rst +++ b/docs/users_guide/8.0.2-notes.rst @@ -171,7 +171,7 @@ Runtime system `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. +- Profiles from the cost-centre profiler now provide source span information. (see :ghc-ticket:`11543`). - The number of threads used for garbage collection is now configurable diff --git a/docs/users_guide/eventlog-formats.rst b/docs/users_guide/eventlog-formats.rst index 8d53f92..f7eb1ca 100644 --- a/docs/users_guide/eventlog-formats.rst +++ b/docs/users_guide/eventlog-formats.rst @@ -46,24 +46,24 @@ A single fixed-width event emitted during program start-up describing the sample * ``String``: Retainer filter * ``String``: Biography filter -Cost center definitions +Cost centre definitions ^^^^^^^^^^^^^^^^^^^^^^^ -A variable-length packet produced once for each cost center, +A variable-length packet produced once for each cost centre, * ``EVENT_HEAP_PROF_COST_CENTRE`` - * ``Word32``: cost center number + * ``Word32``: cost centre number * ``String``: label * ``String``: module * ``String``: source location * ``Word8``: flags - * bit 0: is the cost-center a CAF? + * bit 0: is the cost-centre a CAF? Sample event types ~~~~~~~~~~~~~~~~~~ -A sample (consisting of a list of break-down classes, e.g. cost centers, and +A sample (consisting of a list of break-down classes, e.g. cost centres, and heap residency sizes), is to be encoded in the body of one or more events. We mark the beginning of a new sample with an ``EVENT_HEAP_PROF_SAMPLE_BEGIN`` @@ -78,17 +78,17 @@ in length a single sample may need to be split among multiple determined by the break-down type. -Cost-center break-down +Cost-centre break-down ^^^^^^^^^^^^^^^^^^^^^^ A variable-length packet encoding a heap profile sample broken down by, - * cost-center (``-hc``) + * cost-centre (``-hc``) * ``EVENT_HEAP_PROF_SAMPLE_COST_CENTRE`` * ``Word8``: Profile ID * ``Word64``: heap residency in bytes * ``Word8``: stack depth - * ``Word32[]``: cost center stack starting with inner-most (cost center numbers) + * ``Word32[]``: cost centre stack starting with inner-most (cost centre numbers) String break-down diff --git a/docs/users_guide/profiling.rst b/docs/users_guide/profiling.rst index d035cc5..cf345ed 100644 --- a/docs/users_guide/profiling.rst +++ b/docs/users_guide/profiling.rst @@ -419,11 +419,11 @@ enclosed between ``+RTS ... -RTS`` as usual): .. rts-flag:: -po ⟨stem⟩ The :rts-flag:`-po` option overrides the stem used to form the output file - paths for the cost-center profiler (see :rts-flag:`-p` and :rts-flag:`-pj` + paths for the cost-centre profiler (see :rts-flag:`-p` and :rts-flag:`-pj` flags above) and heap profiler (see :rts-flag:`-h`). For instance, running a program with ``+RTS -h -p -pohello-world`` would - produce a heap profile named :file:`hello-world.hp` and a cost-center + produce a heap profile named :file:`hello-world.hp` and a cost-centre profile named :file:`hello-world.prof`. .. rts-flag:: -V @@ -490,7 +490,7 @@ tree-like object (which we'll call a "cost-centre stack" here) with the following properties, ``id`` (integral number) - The ``id`` of a cost-center listed in the ``cost_centres`` list. + The ``id`` of a cost-centre listed in the ``cost_centres`` list. ``entries`` (integral number) How many times was this cost-centre entered? ``ticks`` (integral number) From git at git.haskell.org Mon May 8 21:39:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 May 2017 21:39:44 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: users-guide: Fix a variety of warnings (cead1b7) Message-ID: <20170508213944.D2DE53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/cead1b7043bbc594a1e569f2bf3cbda39c514b95/ghc >--------------------------------------------------------------- commit cead1b7043bbc594a1e569f2bf3cbda39c514b95 Author: Ben Gamari Date: Mon May 8 17:35:05 2017 -0400 users-guide: Fix a variety of warnings Including #13665. (cherry picked from commit 476307cee7ff142b0eff91d45fddf17775417814) >--------------------------------------------------------------- cead1b7043bbc594a1e569f2bf3cbda39c514b95 docs/users_guide/8.2.1-notes.rst | 3 ++- docs/users_guide/eventlog-formats.rst | 3 +++ docs/users_guide/glasgow_exts.rst | 2 +- docs/users_guide/using-optimisation.rst | 3 +-- docs/users_guide/using-warnings.rst | 2 ++ 5 files changed, 9 insertions(+), 4 deletions(-) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index 3cf3833..a9ed1cd 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -418,7 +418,8 @@ filepath ghc ~~~ -- +- Version number 8.2.1 + ghc-boot ~~~~~~~~ diff --git a/docs/users_guide/eventlog-formats.rst b/docs/users_guide/eventlog-formats.rst index f7eb1ca..8b1427d 100644 --- a/docs/users_guide/eventlog-formats.rst +++ b/docs/users_guide/eventlog-formats.rst @@ -32,12 +32,14 @@ A single fixed-width event emitted during program start-up describing the sample * ``Word8``: Profile ID * ``Word64``: Sampling period in nanoseconds * ``Word32``: Sample break-down type. One of, + * ``SAMPLE_TYPE_COST_CENTER`` (output from ``-hc``) * ``SAMPLE_TYPE_CLOSURE_DESCR`` (output from ``-hd``) * ``SAMPLE_TYPE_RETAINER`` (output from ``-hr``) * ``SAMPLE_TYPE_MODULE`` (output from ``-hm``) * ``SAMPLE_TYPE_TYPE_DESCR`` (output from ``-hy``) * ``SAMPLE_TYPE_BIOGRAPHY`` (output from ``-hb``) + * ``String``: Module filter * ``String``: Closure description filter * ``String``: Type description filter @@ -57,6 +59,7 @@ A variable-length packet produced once for each cost centre, * ``String``: module * ``String``: source location * ``Word8``: flags + * bit 0: is the cost-centre a CAF? diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 19951c4..89b243b 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -10450,7 +10450,7 @@ for constructing pretty-printed error messages, :: | ErrorMessage :<>: ErrorMessage -- Put two chunks of error message next to each other | ErrorMessage :$$: ErrorMessage -- Put two chunks of error message above each other -in the ``GHC.TypeLits`` :base-ref:`module `. +in the ``GHC.TypeLits`` :base-ref:`module `. For instance, we might use this interface to provide a more useful error message for applications of ``show`` on unsaturated functions like this, :: diff --git a/docs/users_guide/using-optimisation.rst b/docs/users_guide/using-optimisation.rst index 3ca08c9..dbdd957 100644 --- a/docs/users_guide/using-optimisation.rst +++ b/docs/users_guide/using-optimisation.rst @@ -108,8 +108,7 @@ The easiest way to see what ``-O`` (etc.) “really mean” is to run with These flags turn on and off individual optimisations. Flags marked as on by default are enabled by ``-O``, and as such you shouldn't need to set any of them explicitly. A flag ``-fwombat`` can be negated -by saying ``-fno-wombat``. See :ref:`options-f-compact` for a compact -list. +by saying ``-fno-wombat``. .. ghc-flag:: -fcase-merge diff --git a/docs/users_guide/using-warnings.rst b/docs/users_guide/using-warnings.rst index 21594ec..ed2b12b 100644 --- a/docs/users_guide/using-warnings.rst +++ b/docs/users_guide/using-warnings.rst @@ -104,6 +104,7 @@ to abort. warnings when doing batch compilation. .. ghc-flag:: -Werror= + :noindex: :implies: ``-W`` @@ -116,6 +117,7 @@ to abort. default, but can be useful to negate a :ghc-flag:`-Werror` flag. .. ghc-flag:: -Wwarn= + :noindex: Causes a specific warning to be treated as normal warning, not fatal error. From git at git.haskell.org Tue May 9 02:27:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 May 2017 02:27:00 +0000 (UTC) Subject: [commit: ghc] master: OptCoercion: Ensure that TyConApps match in arity (87ff5d4) Message-ID: <20170509022700.781333A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/87ff5d4f0f812bad118600df0156f980b91191c5/ghc >--------------------------------------------------------------- commit 87ff5d4f0f812bad118600df0156f980b91191c5 Author: Ben Gamari Date: Mon May 8 17:40:50 2017 -0400 OptCoercion: Ensure that TyConApps match in arity Previously OptCoercion would potentially change the type of UnivCo coercions of the shape, ``` co :: TyCon arg1 ... argN ~ TyCon arg1' ... argN' ``` where the arities of the left and right applications differ. In this case we would try to zip the two argument lists, meaning that one would get truncated. One would think this could never happen since it implies we are applying the same TyCon to two different numbers of arguments. However, it does arise in the case of applications of the `Any` tycon, which arises from the typechecker (in `Data.Typeable.Internal`) where we end up with an `UnsafeCo`, ``` co :: Any (Any -> Any) Any ~ Any (Any -> Any) ``` Test Plan: Validate Reviewers: simonpj, austin, goldfire Reviewed By: simonpj Subscribers: rwbarton, thomie GHC Trac Issues: #13658 Differential Revision: https://phabricator.haskell.org/D3545 >--------------------------------------------------------------- 87ff5d4f0f812bad118600df0156f980b91191c5 compiler/types/OptCoercion.hs | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/compiler/types/OptCoercion.hs b/compiler/types/OptCoercion.hs index b1aa646..17ab302 100644 --- a/compiler/types/OptCoercion.hs +++ b/compiler/types/OptCoercion.hs @@ -364,6 +364,20 @@ opt_phantom env sym co where Pair ty1 ty2 = coercionKind co +{- Note [Differing kinds] + ~~~~~~~~~~~~~~~~~~~~~~ +The two types may not have the same kind (although that would be very unusual). +But even if they have the same kind, and the same type constructor, the number +of arguments in a `CoTyConApp` can differ. Consider + + Any :: forall k. k + + Any * Int :: * + Any (*->*) Maybe Int :: * + +Hence the need to compare argument lengths; see Trac #13658 + -} + opt_univ :: LiftingContext -> SymFlag -> UnivCoProvenance -> Role -> Type -> Type -> Coercion opt_univ env sym (PhantomProv h) _r ty1 ty2 @@ -378,6 +392,7 @@ opt_univ env sym prov role oty1 oty2 | Just (tc1, tys1) <- splitTyConApp_maybe oty1 , Just (tc2, tys2) <- splitTyConApp_maybe oty2 , tc1 == tc2 + , equalLength tys1 tys2 -- see Note [Differing kinds] -- NB: prov must not be the two interesting ones (ProofIrrel & Phantom); -- Phantom is already taken care of, and ProofIrrel doesn't relate tyconapps = let roles = tyConRolesX role tc1 From git at git.haskell.org Tue May 9 02:27:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 May 2017 02:27:03 +0000 (UTC) Subject: [commit: ghc] master: Optimize casMutVar# for single-threaded RTS (ff7a3c4) Message-ID: <20170509022703.328D03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ff7a3c4f9034af0aca1119c1c1e8f7187460bbad/ghc >--------------------------------------------------------------- commit ff7a3c4f9034af0aca1119c1c1e8f7187460bbad Author: David Feuer Date: Mon May 8 17:44:37 2017 -0400 Optimize casMutVar# for single-threaded RTS The single-threaded RTS shouldn't actually need to use CAS to implement `casMutVar#`; there are no other threads to coordinate with. Reviewers: austin, bgamari, erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3544 >--------------------------------------------------------------- ff7a3c4f9034af0aca1119c1c1e8f7187460bbad rts/PrimOps.cmm | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm index 7dd88b8..dddba39 100644 --- a/rts/PrimOps.cmm +++ b/rts/PrimOps.cmm @@ -528,6 +528,7 @@ stg_newMutVarzh ( gcptr init ) stg_casMutVarzh ( gcptr mv, gcptr old, gcptr new ) /* MutVar# s a -> a -> a -> State# s -> (# State#, Int#, Any a #) */ { +#if defined(THREADED_RTS) gcptr h; (h) = prim %cmpxchgW(mv + SIZEOF_StgHeader + OFFSET_StgMutVar_var, old, new); @@ -539,6 +540,20 @@ stg_casMutVarzh ( gcptr mv, gcptr old, gcptr new ) } return (0,new); } +#else + gcptr prev_val; + + prev_val = StgMutVar_var(mv); + if (prev_val != old) { + return (1,prev_val); + } else { + StgMutVar_var(mv) = new; + if (GET_INFO(mv) == stg_MUT_VAR_CLEAN_info) { + ccall dirty_MUT_VAR(BaseReg "ptr", mv "ptr"); + } + return (0,new); + } +#endif } stg_atomicModifyMutVarzh ( gcptr mv, gcptr f ) From git at git.haskell.org Tue May 9 02:27:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 May 2017 02:27:05 +0000 (UTC) Subject: [commit: ghc] master: Fix Raspberry Pi (dc3b4af) Message-ID: <20170509022705.DE1C43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dc3b4af6d0c38ced4f0becf575474a1c1b08f794/ghc >--------------------------------------------------------------- commit dc3b4af6d0c38ced4f0becf575474a1c1b08f794 Author: Moritz Angermann Date: Mon May 8 17:45:18 2017 -0400 Fix Raspberry Pi This is two fold: - We did not catch all ARM_ARCH_6 defines. Specifically not `6K` and `6KZ`, which is what llvm seems to use these days for `arm-none-linux-gnueabihf` (e.g. the triple that's used for raspbian as well). Without it, ghc assums we want to compile against some armv7 system, which raspbian is not (it is armv6 for maximum compatibility across the pi family, compromising on using armv7 and up features). - We stop forcing the -m and -arch flags on macOS. This is troublesome, as compiling for a 32bit system (e.g. raspberry pi, on a x86_64 macOS system results in the `-m64` flag being passed to to clang as well, which in turn figures out that you likely want 64bit, and rewrites your taret from `arm-none-linux-gnueabihf` to `aarch64-none-linux-gnueabihf`, which is definetly not what you want. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, erikd Differential Revision: https://phabricator.haskell.org/D3546 >--------------------------------------------------------------- dc3b4af6d0c38ced4f0becf575474a1c1b08f794 aclocal.m4 | 14 ++------------ 1 file changed, 2 insertions(+), 12 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index dfb7892..d874d41 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -390,6 +390,8 @@ AC_DEFUN([GET_ARM_ISA], defined(__ARM_ARCH_6T2__) || \ defined(__ARM_ARCH_6Z__) || \ defined(__ARM_ARCH_6ZK__) || \ + defined(__ARM_ARCH_6K__) || \ + defined(__ARM_ARCH_6KZ__) || \ defined(__ARM_ARCH_6M__) return 0; #else @@ -585,18 +587,6 @@ AC_DEFUN([FPTOOLS_SET_C_LD_FLAGS], i386-portbld-freebsd*) $2="$$2 -march=i686" ;; - i386-apple-darwin) - $2="$$2 -m32" - $3="$$3 -m32" - $4="$$4 -arch i386" - $5="$$5 -m32" - ;; - x86_64-apple-darwin) - $2="$$2 -m64" - $3="$$3 -m64" - $4="$$4 -arch x86_64" - $5="$$5 -m64" - ;; x86_64-unknown-solaris2) $2="$$2 -m64" $3="$$3 -m64" From git at git.haskell.org Tue May 9 02:27:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 May 2017 02:27:09 +0000 (UTC) Subject: [commit: ghc] master: Make XNegativeLiterals treat -0.0 as negative 0 (0279b74) Message-ID: <20170509022709.6BAD63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0279b745c29213c479b61f864ca5d3d2ae76ac77/ghc >--------------------------------------------------------------- commit 0279b745c29213c479b61f864ca5d3d2ae76ac77 Author: Nolan Date: Mon May 8 17:46:22 2017 -0400 Make XNegativeLiterals treat -0.0 as negative 0 Reviewers: austin, goldfire, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, mpickering GHC Trac Issues: #13211 Differential Revision: https://phabricator.haskell.org/D3543 >--------------------------------------------------------------- 0279b745c29213c479b61f864ca5d3d2ae76ac77 compiler/basicTypes/BasicTypes.hs | 62 +++++++++++++++++++--- compiler/deSugar/Check.hs | 20 ++++--- compiler/deSugar/DsExpr.hs | 4 +- compiler/deSugar/DsMeta.hs | 7 +-- compiler/deSugar/Match.hs | 8 +-- compiler/deSugar/MatchLit.hs | 21 ++++---- compiler/hsSyn/Convert.hs | 11 ++-- compiler/hsSyn/HsLit.hs | 32 ++++++----- compiler/hsSyn/HsUtils.hs | 10 ++-- compiler/parser/Lexer.x | 29 ++++++---- compiler/parser/Parser.y | 28 +++++----- compiler/rename/RnExpr.hs | 7 ++- compiler/rename/RnPat.hs | 60 ++++++++++++++++----- compiler/typecheck/Inst.hs | 6 +-- compiler/typecheck/TcGenDeriv.hs | 9 ++-- compiler/typecheck/TcHsSyn.hs | 12 ++--- .../ghc-api/annotations-literals/literals.stdout | 12 ++--- .../tests/ghc-api/annotations-literals/parsed.hs | 4 +- testsuite/tests/parser/should_run/NegativeZero.hs | 25 +++++++++ .../should_run/NegativeZero.stdout} | 1 + testsuite/tests/parser/should_run/all.T | 1 + testsuite/tests/perf/compiler/all.T | 6 ++- 22 files changed, 253 insertions(+), 122 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 0279b745c29213c479b61f864ca5d3d2ae76ac77 From git at git.haskell.org Tue May 9 02:27:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 May 2017 02:27:12 +0000 (UTC) Subject: [commit: ghc] master: Add a failing test for T13644 (c5b28e0) Message-ID: <20170509022712.E4F063A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c5b28e06cc71cba56153e59e2958f24cdf183fb9/ghc >--------------------------------------------------------------- commit c5b28e06cc71cba56153e59e2958f24cdf183fb9 Author: Matthew Pickering Date: Mon May 8 17:46:39 2017 -0400 Add a failing test for T13644 The problem originates in TcPat.find_field_ty but I don't know how to clearnly fix it. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13644 Differential Revision: https://phabricator.haskell.org/D3535 >--------------------------------------------------------------- c5b28e06cc71cba56153e59e2958f24cdf183fb9 testsuite/tests/rename/should_fail/T13644.hs | 6 ++++++ testsuite/tests/rename/should_fail/T13644.stderr | 6 ++++++ testsuite/tests/rename/should_fail/T13644A.hs | 10 ++++++++++ testsuite/tests/rename/should_fail/T13644B.hs | 3 +++ testsuite/tests/rename/should_fail/T13644C.hs | 3 +++ testsuite/tests/rename/should_fail/all.T | 1 + 6 files changed, 29 insertions(+) diff --git a/testsuite/tests/rename/should_fail/T13644.hs b/testsuite/tests/rename/should_fail/T13644.hs new file mode 100644 index 0000000..14a2049 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T13644.hs @@ -0,0 +1,6 @@ +module T13644 where + +import T13644A + +baseENDECfuncs :: FuncId -> () +baseENDECfuncs FuncId{ name = nm } = undefined diff --git a/testsuite/tests/rename/should_fail/T13644.stderr b/testsuite/tests/rename/should_fail/T13644.stderr new file mode 100644 index 0000000..8443993 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T13644.stderr @@ -0,0 +1,6 @@ + +T13644.hs:6:24: error: + • Constructor ‘FuncId’ does not have field ‘name’ + • In the pattern: FuncId {name = nm} + In an equation for ‘baseENDECfuncs’: + baseENDECfuncs FuncId {name = nm} = undefined diff --git a/testsuite/tests/rename/should_fail/T13644A.hs b/testsuite/tests/rename/should_fail/T13644A.hs new file mode 100644 index 0000000..7838513 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T13644A.hs @@ -0,0 +1,10 @@ +module T13644A +( + FuncId(FuncId) +, module X +) +where + +import T13644C as X + +import T13644B diff --git a/testsuite/tests/rename/should_fail/T13644B.hs b/testsuite/tests/rename/should_fail/T13644B.hs new file mode 100644 index 0000000..72913e0 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T13644B.hs @@ -0,0 +1,3 @@ +module T13644B where + +data FuncId = FuncId { name :: () } diff --git a/testsuite/tests/rename/should_fail/T13644C.hs b/testsuite/tests/rename/should_fail/T13644C.hs new file mode 100644 index 0000000..530d663 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T13644C.hs @@ -0,0 +1,3 @@ +module T13644C where + +data T = T { name :: () } diff --git a/testsuite/tests/rename/should_fail/all.T b/testsuite/tests/rename/should_fail/all.T index 4782685..517d23d 100644 --- a/testsuite/tests/rename/should_fail/all.T +++ b/testsuite/tests/rename/should_fail/all.T @@ -125,3 +125,4 @@ test('T12681', normal, multimod_compile_fail, ['T12681','-v0']) test('T12686', normal, compile_fail, ['']) test('T11592', normal, compile_fail, ['']) test('T12879', normal, compile_fail, ['']) +test('T13644', expect_broken(13644), multimod_compile_fail, ['T13644','-v0']) From git at git.haskell.org Tue May 9 02:27:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 May 2017 02:27:19 +0000 (UTC) Subject: [commit: ghc] master: Treat banged bindings as FunBinds (3729953) Message-ID: <20170509022719.1CA233A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/372995364c52eef15066132d7d1ea8b6760034e6/ghc >--------------------------------------------------------------- commit 372995364c52eef15066132d7d1ea8b6760034e6 Author: Ben Gamari Date: Mon May 8 17:47:19 2017 -0400 Treat banged bindings as FunBinds This reworks the HsSyn representation to make banged variable patterns (e.g. !x = e) be represented as FunBinds instead of PatBinds, adding a flag to FunRhs to record the bang. Fixes #13594. Reviewers: austin, goldfire, alanz, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D3525 >--------------------------------------------------------------- 372995364c52eef15066132d7d1ea8b6760034e6 compiler/deSugar/Check.hs | 6 ++-- compiler/deSugar/DsBinds.hs | 4 +-- compiler/deSugar/DsExpr.hs | 2 +- compiler/hsSyn/Convert.hs | 6 ++-- compiler/hsSyn/HsBinds.hs | 40 ++++++++++++++++++++-- compiler/hsSyn/HsExpr.hs | 38 ++++++++++++-------- compiler/hsSyn/HsUtils.hs | 8 +++-- compiler/parser/Parser.y | 34 +++++++++++------- compiler/parser/RdrHsSyn.hs | 16 +++++---- compiler/rename/RnBinds.hs | 8 ++--- compiler/typecheck/TcGenDeriv.hs | 10 +++--- compiler/typecheck/TcGenFunctor.hs | 13 ++++--- compiler/typecheck/TcInstDcls.hs | 2 +- compiler/typecheck/TcMatches.hs | 3 +- compiler/typecheck/TcPatSyn.hs | 4 +-- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcTyDecls.hs | 4 +-- .../parser/should_compile/DumpParsedAst.stderr | 3 +- .../parser/should_compile/DumpRenamedAst.stderr | 3 +- .../should_compile/DumpTypecheckedAst.stderr | 3 +- testsuite/tests/parser/should_compile/T13594.hs | 8 +++++ testsuite/tests/parser/should_compile/all.T | 1 + 22 files changed, 144 insertions(+), 74 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 372995364c52eef15066132d7d1ea8b6760034e6 From git at git.haskell.org Tue May 9 02:27:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 May 2017 02:27:15 +0000 (UTC) Subject: [commit: ghc] master: Dataflow: use IntSet for mkDepBlocks (b99bae6) Message-ID: <20170509022715.9BCB53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b99bae6d132e083b73283963be85932596341ddd/ghc >--------------------------------------------------------------- commit b99bae6d132e083b73283963be85932596341ddd Author: Michal Terepeta Date: Mon May 8 17:47:02 2017 -0400 Dataflow: use IntSet for mkDepBlocks Using `IntSet` instead of `[Int]` is nicer since it gets rid of appending to a list (in the backward case) and folding over it is ordered. I also added a comment about how `mkDepBlocks` works since its behavior can be a bit surprising at first sight (it took me some time to see that it's doing the right thing ;) Signed-off-by: Michal Terepeta Test Plan: ./validate Reviewers: austin, bgamari, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3530 >--------------------------------------------------------------- b99bae6d132e083b73283963be85932596341ddd compiler/cmm/Hoopl/Dataflow.hs | 60 +++++++++++++++++++++++++----------------- 1 file changed, 36 insertions(+), 24 deletions(-) diff --git a/compiler/cmm/Hoopl/Dataflow.hs b/compiler/cmm/Hoopl/Dataflow.hs index b98c681..197a9c4 100644 --- a/compiler/cmm/Hoopl/Dataflow.hs +++ b/compiler/cmm/Hoopl/Dataflow.hs @@ -35,6 +35,8 @@ import Cmm import Data.Array import Data.List import Data.Maybe +import Data.IntSet (IntSet) +import qualified Data.IntSet as IntSet -- Hide definitions from Hoopl's Dataflow module. import Compiler.Hoopl hiding ( DataflowLattice, OldFact, NewFact, JoinFun @@ -215,42 +217,52 @@ sortBlocks direction entries blockmap = -- reverse of what is used for the forward one. --- | construct a mapping from L -> block indices. If the fact for L --- changes, re-analyse the given blocks. -mkDepBlocks :: NonLocal n => Direction -> [Block n C C] -> LabelMap [Int] +-- | Construct a mapping from a @Label@ to the block indexes that should be +-- re-analyzed if the facts at that @Label@ change. +-- +-- Note that we're considering here the entry point of the block, so if the +-- facts change at the entry: +-- * for a backward analysis we need to re-analyze all the predecessors, but +-- * for a forward analysis, we only need to re-analyze the current block +-- (and that will in turn propagate facts into its successors). +mkDepBlocks :: Direction -> [CmmBlock] -> LabelMap IntSet mkDepBlocks Fwd blocks = go blocks 0 mapEmpty - where go [] !_ m = m - go (b:bs) !n m = go bs (n+1) $! mapInsert (entryLabel b) [n] m + where + go [] !_ !dep_map = dep_map + go (b:bs) !n !dep_map = + go bs (n + 1) $ mapInsert (entryLabel b) (IntSet.singleton n) dep_map mkDepBlocks Bwd blocks = go blocks 0 mapEmpty - where go [] !_ m = m - go (b:bs) !n m = go bs (n+1) $! go' (successors b) m - where go' [] m = m - go' (l:ls) m = go' ls (mapInsertWith (++) l [n] m) - + where + go [] !_ !dep_map = dep_map + go (b:bs) !n !dep_map = + let insert m l = mapInsertWith IntSet.union l (IntSet.singleton n) m + in go bs (n + 1) $ foldl' insert dep_map (successors b) -- | After some new facts have been generated by analysing a block, we -- fold this function over them to generate (a) a list of block -- indices to (re-)analyse, and (b) the new FactBase. --- -updateFact :: JoinFun f -> LabelMap [Int] - -> Label -> f -- out fact - -> (IntHeap, FactBase f) - -> (IntHeap, FactBase f) - +updateFact + :: JoinFun f + -> LabelMap IntSet + -> Label + -> f -- out fact + -> (IntHeap, FactBase f) + -> (IntHeap, FactBase f) updateFact fact_join dep_blocks lbl new_fact (todo, fbase) = case lookupFact lbl fbase of - Nothing -> let !z = mapInsert lbl new_fact fbase in (changed, z) - -- Note [no old fact] + Nothing -> + -- Note [No old fact] + let !z = mapInsert lbl new_fact fbase in (changed, z) Just old_fact -> - case fact_join (OldFact old_fact) (NewFact new_fact) of - (NotChanged _) -> (todo, fbase) - (Changed f) -> let !z = mapInsert lbl f fbase in (changed, z) + case fact_join (OldFact old_fact) (NewFact new_fact) of + (NotChanged _) -> (todo, fbase) + (Changed f) -> let !z = mapInsert lbl f fbase in (changed, z) where - changed = foldr insertIntHeap todo $ - mapFindWithDefault [] lbl dep_blocks + changed = IntSet.foldr insertIntHeap todo $ + mapFindWithDefault IntSet.empty lbl dep_blocks {- -Note [no old fact] +Note [No old fact] We know that the new_fact is >= _|_, so we don't need to join. However, if the new fact is also _|_, and we have already analysed its block, From git at git.haskell.org Tue May 9 03:38:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 May 2017 03:38:57 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Fix attribution of "Don't seq unfoldings" regression (85bfd0c) Message-ID: <20170509033857.2E77E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/85bfd0c384a1ea12ebb8aa8e56e9dbcab6d60f4c/ghc >--------------------------------------------------------------- commit 85bfd0c384a1ea12ebb8aa8e56e9dbcab6d60f4c Author: Ben Gamari Date: Mon May 8 23:38:16 2017 -0400 testsuite: Fix attribution of "Don't seq unfoldings" regression >--------------------------------------------------------------- 85bfd0c384a1ea12ebb8aa8e56e9dbcab6d60f4c testsuite/tests/perf/compiler/all.T | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index a5ef47e..a5dd1ae 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -755,7 +755,7 @@ test('T9675', # 2016-03-14 38776008 Final demand analyzer run # 2016-04-01 29871032 Fix leaks in demand analysis # 2016-04-30 17675240 Fix leaks in tidy unfoldings - # 2017-05-08 25381032 Fix negative zero (see #13211) + # 2017-05-08 25381032 CoreTidy: Don't seq unfoldings (wordsize(32), 18043224, 15) # 2015-07-11 15341228 (x86/Linux, 64-bit machine) use +RTS -G1 # 2016-04-06 18043224 (x86/Linux, 64-bit machine) @@ -773,7 +773,7 @@ test('T9675', # 2016-04-14 144 Final demand analyzer run # 2016-07-26 121 Unboxed sums? # 2017-04-30 63 Fix leaks in tidy unfoldings - # 2017-05-08 94 Fix negative zero (see #13211) + # 2017-05-08 94 CoreTidy: Don't seq unfoldings (wordsize(32), 56, 15) # 2015-07-11 56 (x86/Linux, 64-bit machine) use +RTS -G1 ]), From git at git.haskell.org Tue May 9 09:44:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 May 2017 09:44:24 +0000 (UTC) Subject: [commit: ghc] master: Use mkSymCo in OptCoercion.wrapSym (d46a510) Message-ID: <20170509094424.CBB663A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d46a5102e0911e96a85434e46bbfe8b9ccc86471/ghc >--------------------------------------------------------------- commit d46a5102e0911e96a85434e46bbfe8b9ccc86471 Author: Simon Peyton Jones Date: Mon May 8 13:31:11 2017 +0100 Use mkSymCo in OptCoercion.wrapSym Always use the smart constructor! Richard and I came across this omission when looking at something else. >--------------------------------------------------------------- d46a5102e0911e96a85434e46bbfe8b9ccc86471 compiler/types/OptCoercion.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/types/OptCoercion.hs b/compiler/types/OptCoercion.hs index 17ab302..871840e 100644 --- a/compiler/types/OptCoercion.hs +++ b/compiler/types/OptCoercion.hs @@ -794,7 +794,7 @@ checkAxInstCo _ = Nothing ----------- wrapSym :: SymFlag -> Coercion -> Coercion -wrapSym sym co | sym = SymCo co +wrapSym sym co | sym = mkSymCo co | otherwise = co -- | Conditionally set a role to be representational From git at git.haskell.org Tue May 9 09:44:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 May 2017 09:44:28 +0000 (UTC) Subject: [commit: ghc] master: Don't warn about variable-free strict pattern bindings (549c8b3) Message-ID: <20170509094428.383873A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/549c8b33da25371ab1aa1818ef27fc418252e667/ghc >--------------------------------------------------------------- commit 549c8b33da25371ab1aa1818ef27fc418252e667 Author: Simon Peyton Jones Date: Mon May 8 14:04:34 2017 +0100 Don't warn about variable-free strict pattern bindings See Trac #13646 and the new Note [Pattern bindings that bind no variables] >--------------------------------------------------------------- 549c8b33da25371ab1aa1818ef27fc418252e667 compiler/rename/RnBinds.hs | 48 +++++++++++++++------- docs/users_guide/using-warnings.rst | 10 +++-- testsuite/tests/rename/should_compile/T13646.hs | 15 +++++++ .../tests/rename/should_compile/T13646.stderr | 3 ++ testsuite/tests/rename/should_compile/all.T | 1 + 5 files changed, 58 insertions(+), 19 deletions(-) diff --git a/compiler/rename/RnBinds.hs b/compiler/rename/RnBinds.hs index d78ed93..0b4cbeb 100644 --- a/compiler/rename/RnBinds.hs +++ b/compiler/rename/RnBinds.hs @@ -456,21 +456,22 @@ rnBind _ bind@(PatBind { pat_lhs = pat -- As well as dependency analysis, we need these for the -- MonoLocalBinds test in TcBinds.decideGeneralisationPlan bndrs = collectPatBinders pat - bind' = bind { pat_rhs = grhss', - pat_rhs_ty = placeHolderType, bind_fvs = fvs' } - is_wild_pat = case pat of - L _ (WildPat {}) -> True - L _ (BangPat (L _ (WildPat {}))) -> True -- #9127 - _ -> False - - -- Warn if the pattern binds no variables, except for the - -- entirely-explicit idiom _ = rhs - -- which (a) is not that different from _v = rhs - -- (b) is sometimes used to give a type sig for, - -- or an occurrence of, a variable on the RHS + bind' = bind { pat_rhs = grhss' + , pat_rhs_ty = placeHolderType, bind_fvs = fvs' } + + ok_nobind_pat + = -- See Note [Pattern bindings that bind no variables] + case pat of + L _ (WildPat {}) -> True + L _ (BangPat {}) -> True -- #9127, #13646 + _ -> False + + -- Warn if the pattern binds no variables + -- See Note [Pattern bindings that bind no variables] ; whenWOptM Opt_WarnUnusedPatternBinds $ - when (null bndrs && not is_wild_pat) $ - addWarn (Reason Opt_WarnUnusedPatternBinds) $ unusedPatBindWarn bind' + when (null bndrs && not ok_nobind_pat) $ + addWarn (Reason Opt_WarnUnusedPatternBinds) $ + unusedPatBindWarn bind' ; fvs' `seq` -- See Note [Free-variable space leak] return (bind', bndrs, all_fvs) } @@ -505,7 +506,24 @@ rnBind sig_fn (PatSynBind bind) rnBind _ b = pprPanic "rnBind" (ppr b) -{- +{- Note [Pattern bindings that bind no variables] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Generally, we want to warn about pattern bindings like + Just _ = e +because they don't do anything! But we have two exceptions: + +* A wildcard pattern + _ = rhs + which (a) is not that different from _v = rhs + (b) is sometimes used to give a type sig for, + or an occurrence of, a variable on the RHS + +* A strict patten binding; that is, one with an outermost bang + !Just _ = e + This can fail, so unlike the lazy variant, it is not a no-op. + Moreover, Trac #13646 argues that even for single constructor + types, you might want to write the constructor. See also #9127. + Note [Free-variable space leak] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We have diff --git a/docs/users_guide/using-warnings.rst b/docs/users_guide/using-warnings.rst index ed2b12b..6a42f54 100644 --- a/docs/users_guide/using-warnings.rst +++ b/docs/users_guide/using-warnings.rst @@ -902,18 +902,20 @@ of ``-W(no-)*``. single: binds, unused Warn if a pattern binding binds no variables at all, unless it is a - lone, possibly-banged, wild-card pattern. For example: :: + lone wild-card pattern, or a banged pattern. For example: :: Just _ = rhs3 -- Warning: unused pattern binding (_, _) = rhs4 -- Warning: unused pattern binding _ = rhs3 -- No warning: lone wild-card pattern - !_ = rhs4 -- No warning: banged wild-card pattern; behaves like seq + !() = rhs4 -- No warning: banged pattern; behaves like seq + In general a lazy pattern binding `p = e` is a no-op if `p` does not + bind any variables. The motivation for allowing lone wild-card patterns is they are not very different from ``_v = rhs3``, which elicits no warning; and they can be useful to add a type constraint, e.g. ``_ = x::Int``. A - lone banged wild-card pattern is useful as an alternative (to - ``seq``) way to force evaluation. + banged pattern (see :ref:`bang-patterns`) is *not* a no-op, because + it forces evaluation, and is useful as an alternative to ``seq``. .. ghc-flag:: -Wunused-imports diff --git a/testsuite/tests/rename/should_compile/T13646.hs b/testsuite/tests/rename/should_compile/T13646.hs new file mode 100644 index 0000000..d2d8279 --- /dev/null +++ b/testsuite/tests/rename/should_compile/T13646.hs @@ -0,0 +1,15 @@ +{-# OPTIONS_GHC -Wall #-} +{-# LANGUAGE BangPatterns #-} + +module T13646 where + +import Control.Exception + +foo :: IO () +foo = do let !() = assert False () + -- Should not give a warning + + let () = assert False () + -- Should give a warning + + pure () diff --git a/testsuite/tests/rename/should_compile/T13646.stderr b/testsuite/tests/rename/should_compile/T13646.stderr new file mode 100644 index 0000000..ad23c44 --- /dev/null +++ b/testsuite/tests/rename/should_compile/T13646.stderr @@ -0,0 +1,3 @@ + +T13646.hs:12:14: warning: [-Wunused-pattern-binds (in -Wextra, -Wunused-binds)] + This pattern-binding binds no variables: () = assert False () diff --git a/testsuite/tests/rename/should_compile/all.T b/testsuite/tests/rename/should_compile/all.T index f6b71fd..e7ad719 100644 --- a/testsuite/tests/rename/should_compile/all.T +++ b/testsuite/tests/rename/should_compile/all.T @@ -150,3 +150,4 @@ test('T12533', normal, compile, ['']) test('T12597', normal, compile, ['']) test('T12548', normal, compile, ['']) test('T13132', normal, compile, ['']) +test('T13646', normal, compile, ['']) From git at git.haskell.org Tue May 9 09:44:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 May 2017 09:44:34 +0000 (UTC) Subject: [commit: ghc] master: Make CallInfo into a data type with fields (cb5ca5f) Message-ID: <20170509094434.6C7003A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cb5ca5f39c2ad26608516ee4248b9ddea31a1d5a/ghc >--------------------------------------------------------------- commit cb5ca5f39c2ad26608516ee4248b9ddea31a1d5a Author: Simon Peyton Jones Date: Mon May 8 16:50:37 2017 +0100 Make CallInfo into a data type with fields Simple refactor, no change in behaviour >--------------------------------------------------------------- cb5ca5f39c2ad26608516ee4248b9ddea31a1d5a compiler/specialise/Specialise.hs | 57 ++++++++++++++++++++++++--------------- 1 file changed, 36 insertions(+), 21 deletions(-) diff --git a/compiler/specialise/Specialise.hs b/compiler/specialise/Specialise.hs index 37afca5..66301a5 100644 --- a/compiler/specialise/Specialise.hs +++ b/compiler/specialise/Specialise.hs @@ -1224,7 +1224,7 @@ specCalls mb_mod env rules_for_me calls_for_me fn rhs -> SpecM (Maybe ((Id,CoreExpr), -- Specialised definition UsageDetails, -- Usage details from specialised body CoreRule)) -- Info for the Id's SpecEnv - spec_call _call_info@(CallKey call_ts, (call_ds, _)) + spec_call (CI { ci_key = CallKey call_ts, ci_args = call_ds }) = ASSERT( call_ts `lengthIs` n_tyvars && call_ds `lengthIs` n_dicts ) -- Suppose f's defn is f = /\ a b c -> \ d1 d2 -> rhs @@ -1768,8 +1768,6 @@ instance Outputable UsageDetails where -- variables (both type variables and dictionaries) type DictBind = (CoreBind, VarSet) -type DictExpr = CoreExpr - emptyUDs :: UsageDetails emptyUDs = MkUD { ud_binds = emptyBag, ud_calls = emptyDVarEnv } @@ -1778,13 +1776,25 @@ type CallDetails = DIdEnv CallInfoSet -- The order of specialized binds and rules depends on how we linearize -- CallDetails, so to get determinism we must use a deterministic set here. -- See Note [Deterministic UniqFM] in UniqDFM -newtype CallKey = CallKey [Maybe Type] - -- Nothing => unconstrained type argument data CallInfoSet = CIS Id (Bag CallInfo) -- The list of types and dictionaries is guaranteed to -- match the type of f +data CallInfo + = CI { ci_key :: CallKey -- Type arguments + , ci_args :: [DictExpr] -- Dictionary arguments + , ci_fvs :: VarSet -- Free vars of the ci_key and ci_args + -- call (including tyvars) + -- [*not* include the main id itself, of course] + } + +newtype CallKey = CallKey [Maybe Type] + -- Nothing => unconstrained type argument + +type DictExpr = CoreExpr + + {- Note [CallInfoSet determinism] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1829,7 +1839,7 @@ ciSetToList (CIS _ b) = snd $ foldrBag combine (emptyTM, []) b -- This is where we eliminate duplicates, recording the CallKeys we've -- already seen in the TrieMap. See Note [CallInfoSet determinism]. combine :: CallInfo -> (CallKeySet, [CallInfo]) -> (CallKeySet, [CallInfo]) - combine ci@(CallKey key, _) (set, acc) + combine ci@(CI { ci_key = CallKey key }) (set, acc) | Just _ <- lookupTM key set = (set, acc) | otherwise = (insertTM key () set, ci:acc) @@ -1839,26 +1849,24 @@ type CallKeySet = ListMap (MaybeMap TypeMap) () ciSetFilter :: (CallInfo -> Bool) -> CallInfoSet -> CallInfoSet ciSetFilter p (CIS id a) = CIS id (filterBag p a) -type CallInfo = (CallKey, ([DictExpr], VarSet)) - -- Range is dict args and the vars of the whole - -- call (including tyvars) - -- [*not* include the main id itself, of course] - instance Outputable CallInfoSet where ppr (CIS fn map) = hang (text "CIS" <+> ppr fn) 2 (ppr map) pprCallInfo :: Id -> CallInfo -> SDoc -pprCallInfo fn (CallKey mb_tys, (_dxs, _)) - = hang (ppr fn) - 2 (fsep (map ppr_call_key_ty mb_tys {- ++ map pprParendExpr _dxs -})) +pprCallInfo fn (CI { ci_key = key }) + = ppr fn <+> ppr key ppr_call_key_ty :: Maybe Type -> SDoc ppr_call_key_ty Nothing = char '_' ppr_call_key_ty (Just ty) = char '@' <+> pprParendType ty instance Outputable CallKey where - ppr (CallKey ts) = ppr ts + ppr (CallKey ts) = brackets (fsep (map ppr_call_key_ty ts)) + +instance Outputable CallInfo where + ppr (CI { ci_key = key, ci_args = args, ci_fvs = fvs }) + = text "CI" <> braces (hsep [ ppr key, ppr args, ppr fvs ]) unionCalls :: CallDetails -> CallDetails -> CallDetails unionCalls c1 c2 = plusDVarEnv_C unionCallInfoSet c1 c2 @@ -1875,14 +1883,16 @@ callDetailsFVs calls = callInfoFVs :: CallInfoSet -> VarSet callInfoFVs (CIS _ call_info) = - foldrBag (\(_, (_,fv)) vs -> unionVarSet fv vs) emptyVarSet call_info + foldrBag (\(CI { ci_fvs = fv }) vs -> unionVarSet fv vs) emptyVarSet call_info ------------------------------------------------------------ singleCall :: Id -> [Maybe Type] -> [DictExpr] -> UsageDetails singleCall id tys dicts = MkUD {ud_binds = emptyBag, ud_calls = unitDVarEnv id $ CIS id $ - unitBag (CallKey tys, (dicts, call_fvs)) } + unitBag (CI { ci_key = CallKey tys + , ci_args = dicts + , ci_fvs = call_fvs }) } where call_fvs = exprsFreeVars dicts `unionVarSet` tys_fvs tys_fvs = tyCoVarsOfTypes (catMaybes tys) @@ -2146,11 +2156,16 @@ callsForMe fn (MkUD { ud_binds = orig_dbs, ud_calls = orig_calls }) filter_dfuns | isDFunId fn = filter ok_call | otherwise = \cs -> cs - ok_call (_, (_,fvs)) = not (fvs `intersectsVarSet` dep_set) + ok_call (CI { ci_fvs = fvs }) = not (fvs `intersectsVarSet` dep_set) ---------------------- splitDictBinds :: Bag DictBind -> IdSet -> (Bag DictBind, Bag DictBind, IdSet) --- Returns (free_dbs, dump_dbs, dump_set) +-- splitDictBinds dbs bndrs returns +-- (free_dbs, dump_dbs, dump_set) +-- where +-- * dump_dbs depends, transitively on bndrs +-- * free_dbs does not depend on bndrs +-- * dump_set = bndrs `union` bndrs(dump_dbs) splitDictBinds dbs bndr_set = foldlBag split_db (emptyBag, emptyBag, bndr_set) dbs -- Important that it's foldl not foldr; @@ -2167,11 +2182,11 @@ splitDictBinds dbs bndr_set ---------------------- deleteCallsMentioning :: VarSet -> CallDetails -> CallDetails --- Remove calls *mentioning* bs +-- Remove calls *mentioning* bs in any way deleteCallsMentioning bs calls = mapDVarEnv (ciSetFilter keep_call) calls where - keep_call (_, (_, fvs)) = not (fvs `intersectsVarSet` bs) + keep_call (CI { ci_fvs = fvs }) = not (fvs `intersectsVarSet` bs) deleteCallsFor :: [Id] -> CallDetails -> CallDetails -- Remove calls *for* bs From git at git.haskell.org Tue May 9 09:44:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 May 2017 09:44:31 +0000 (UTC) Subject: [commit: ghc] master: Add regression test for Trac #13659 (6f26fe7) Message-ID: <20170509094431.A397B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6f26fe79c1952df7881f17cb504c4ecae527def7/ghc >--------------------------------------------------------------- commit 6f26fe79c1952df7881f17cb504c4ecae527def7 Author: Simon Peyton Jones Date: Mon May 8 14:06:01 2017 +0100 Add regression test for Trac #13659 >--------------------------------------------------------------- 6f26fe79c1952df7881f17cb504c4ecae527def7 testsuite/tests/polykinds/T13659.hs | 12 ++++++++++++ testsuite/tests/polykinds/T13659.stderr | 6 ++++++ testsuite/tests/polykinds/all.T | 1 + 3 files changed, 19 insertions(+) diff --git a/testsuite/tests/polykinds/T13659.hs b/testsuite/tests/polykinds/T13659.hs new file mode 100644 index 0000000..199ff08 --- /dev/null +++ b/testsuite/tests/polykinds/T13659.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE GADTs, EmptyDataDecls, TypeFamilies, TypeOperators, DataKinds, FlexibleInstances #-} + +{- Defines a C-like printf function using DataKinds extensions. -} + +module T13659 where + +-- format string parameterized by a list of types +data Format (fmt :: [*]) where + X :: Format '[] -- empty string, i.e. "" + L :: a -> String -> Format '[] -- string literal, e.g. "hello" + S :: a -> Format '[String] -- "%s" + I :: Format a -> Format '[Int, a] -- "%d" diff --git a/testsuite/tests/polykinds/T13659.stderr b/testsuite/tests/polykinds/T13659.stderr new file mode 100644 index 0000000..fac5cbb --- /dev/null +++ b/testsuite/tests/polykinds/T13659.stderr @@ -0,0 +1,6 @@ + +T13659.hs:12:27: error: + • Expected a type, but ‘a’ has kind ‘[*]’ + • In the first argument of ‘Format’, namely ‘'[Int, a]’ + In the type ‘Format '[Int, a]’ + In the definition of data constructor ‘I’ diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index b59cbe6..28d33c1 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -161,3 +161,4 @@ test('T13394', normal, compile, ['']) test('T13371', normal, compile, ['']) test('T13393', normal, compile_fail, ['']) test('T13555', normal, compile_fail, ['']) +test('T13659', normal, compile_fail, ['']) From git at git.haskell.org Tue May 9 09:44:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 May 2017 09:44:37 +0000 (UTC) Subject: [commit: ghc] master: Reset cc_pend_sc flag in dropDerivedCt (43a3168) Message-ID: <20170509094437.A22263A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/43a31683acbe2f8120fbb73fe5a6fd1f5de9db80/ghc >--------------------------------------------------------------- commit 43a31683acbe2f8120fbb73fe5a6fd1f5de9db80 Author: Simon Peyton Jones Date: Tue May 9 09:29:44 2017 +0100 Reset cc_pend_sc flag in dropDerivedCt I'd forgotten to reset this flag to True when dropping Derived constraints, which led to Trac #13662. Easily fixed. >--------------------------------------------------------------- 43a31683acbe2f8120fbb73fe5a6fd1f5de9db80 compiler/typecheck/TcCanonical.hs | 25 ++++++++----- compiler/typecheck/TcRnTypes.hs | 41 +++++++++++++++------- .../tests/indexed-types/should_compile/T13662.hs | 25 +++++++++++++ testsuite/tests/indexed-types/should_compile/all.T | 1 + 4 files changed, 72 insertions(+), 20 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 10f871f..b623541 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -161,18 +161,19 @@ canClass ev cls tys pend_sc ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We need to add superclass constraints for two reasons: -* For givens, they give us a route to to proof. E.g. +* For givens [G], they give us a route to to proof. E.g. f :: Ord a => a -> Bool f x = x == x We get a Wanted (Eq a), which can only be solved from the superclass of the Given (Ord a). -* For wanteds, they may give useful functional dependencies. E.g. +* For wanteds [W], and deriveds [WD], [D], they may give useful + functional dependencies. E.g. class C a b | a -> b where ... class C a b => D a b where ... - Now a Wanted constraint (D Int beta) has (C Int beta) as a superclass + Now a [W] constraint (D Int beta) has (C Int beta) as a superclass and that might tell us about beta, via C's fundeps. We can get this - by generateing a Derived (C Int beta) constraint. It's derived because + by generating a [D] (C Int beta) constraint. It's derived because we don't actually have to cough up any evidence for it; it's only there to generate fundep equalities. @@ -227,12 +228,20 @@ So here's the plan: 4. Go round to (2) again. This loop (2,3,4) is implemented in TcSimplify.simpl_loop. -We try to terminate the loop by flagging which class constraints -(given or wanted) are potentially un-expanded. This is what the -cc_pend_sc flag is for in CDictCan. So in Step 3 we only expand -superclasses for constraints with cc_pend_sc set to true (i.e. +The cc_pend_sc flag in a CDictCan records whether the superclasses of +this constraint have been expanded. Specifically, in Step 3 we only +expand superclasses for constraints with cc_pend_sc set to true (i.e. isPendingScDict holds). +Why do we do this? Two reasons: + +* To avoid repeated work, by repeatedly expanding the superclasses of + same constraint, + +* To terminate the above loop, at least in the -XNoRecursiveSuperClasses + case. If there are recursive superclasses we could, in principle, + expand forever, always encountering new constraints. + When we take a CNonCanonical or CIrredCan, but end up classifying it as a CDictCan, we set the cc_pend_sc flag to False. diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index ba7c44f..7aef4bb 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -1523,14 +1523,14 @@ data Ct -- Atomic canonical constraints = CDictCan { -- e.g. Num xi cc_ev :: CtEvidence, -- See Note [Ct/evidence invariant] + cc_class :: Class, - cc_tyargs :: [Xi], -- cc_tyargs are function-free, hence Xi - cc_pend_sc :: Bool -- True <=> (a) cc_class has superclasses - -- (b) we have not (yet) added those - -- superclasses as Givens - -- NB: cc_pend_sc is used for G/W/D. For W/D the reason - -- we need superclasses is to expose possible improvement - -- via fundeps + cc_tyargs :: [Xi], -- cc_tyargs are function-free, hence Xi + + cc_pend_sc :: Bool -- See Note [The superclass story] in TcCanonical + -- True <=> (a) cc_class has superclasses + -- (b) we have not (yet) added those + -- superclasses as Givens } | CIrredEvCan { -- These stand for yet-unusable predicates @@ -1608,9 +1608,8 @@ holeOcc :: Hole -> OccName holeOcc (ExprHole uv) = unboundVarOcc uv holeOcc (TypeHole occ) = occ -{- -Note [Hole constraints] -~~~~~~~~~~~~~~~~~~~~~~~ +{- Note [Hole constraints] +~~~~~~~~~~~~~~~~~~~~~~~~~~ CHoleCan constraints are used for two kinds of holes, distinguished by cc_hole: @@ -1805,13 +1804,25 @@ 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 + 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 } + ct' = setPendingScDict ct -- See Note [Resetting cc_pend_sc] + +{- Note [Resetting cc_pend_sc] +~~~~~~~~~~~~~~~~~~~~~~~~~~~ +When we discard Derived constraints, in dropDerivedSimples, we must +set the cc_pend_sc flag to True, so that if we re-process this +CDictCan we will re-generate its derived superclasses. Otherwise +we might miss some fundeps. Trac #13662 showed this up. + +See Note [The superclass story] in TcCanonical. +-} + dropDerivedInsols :: Cts -> Cts -- See Note [Dropping derived constraints] @@ -2011,6 +2022,12 @@ isPendingScDict ct@(CDictCan { cc_pend_sc = True }) = Just (ct { cc_pend_sc = False }) isPendingScDict _ = Nothing +setPendingScDict :: Ct -> Ct +-- Set the cc_pend_sc flag to True +setPendingScDict ct@(CDictCan { cc_pend_sc = False }) + = ct { cc_pend_sc = True } +setPendingScDict ct = ct + superClassesMightHelp :: Ct -> Bool -- ^ True if taking superclasses of givens, or of wanteds (to perhaps -- expose more equalities or functional dependencies) might help to diff --git a/testsuite/tests/indexed-types/should_compile/T13662.hs b/testsuite/tests/indexed-types/should_compile/T13662.hs new file mode 100644 index 0000000..5898f25 --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T13662.hs @@ -0,0 +1,25 @@ +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE MultiParamTypeClasses #-} +module T13662 (run) where + +newtype Value a = Value a + +type family Repr (f :: * -> *) a :: * +type instance Repr f Int = f Int + +class (Repr Value i ~ Value ir) => Native i ir where + +instance Native Int Int where + + +fromInt :: (Native i ir) => i -> a +fromInt = undefined + +apply :: (Int -> a -> a) -> a -> a +apply weight = id + +run :: Float -> Float +run = + let weight = \clip v -> fromInt clip * v + in apply weight + diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index 529f7de..00d40ce 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -263,3 +263,4 @@ test('T12538', normal, compile_fail, ['']) test('T13244', normal, compile, ['']) test('T13398a', normal, compile, ['']) test('T13398b', normal, compile, ['']) +test('T13662', normal, compile, ['']) From git at git.haskell.org Tue May 9 21:40:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 May 2017 21:40:52 +0000 (UTC) Subject: [commit: ghc] master: Revert "CoreTidy: Don't seq unfoldings" (8e72a2e) Message-ID: <20170509214052.0B2AA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8e72a2eee29543f8a663256f6b8cf4422692cb3a/ghc >--------------------------------------------------------------- commit 8e72a2eee29543f8a663256f6b8cf4422692cb3a Author: Ben Gamari Date: Tue May 9 16:00:29 2017 -0400 Revert "CoreTidy: Don't seq unfoldings" This reverts commit b3da6a6c3546562d5c5e83b8af5d3fd04c07e0c1 as it reintroduces the original space leak. >--------------------------------------------------------------- 8e72a2eee29543f8a663256f6b8cf4422692cb3a compiler/coreSyn/CoreTidy.hs | 18 +++++++----------- testsuite/tests/perf/compiler/all.T | 6 ++---- 2 files changed, 9 insertions(+), 15 deletions(-) diff --git a/compiler/coreSyn/CoreTidy.hs b/compiler/coreSyn/CoreTidy.hs index 3578b0b..89ce692 100644 --- a/compiler/coreSyn/CoreTidy.hs +++ b/compiler/coreSyn/CoreTidy.hs @@ -15,7 +15,7 @@ module CoreTidy ( #include "HsVersions.h" import CoreSyn -import CoreUnfold ( mkCoreUnfolding ) +import CoreSeq ( seqUnfolding ) import CoreArity import Id import IdInfo @@ -221,21 +221,17 @@ tidyUnfolding tidy_env df@(DFunUnfolding { df_bndrs = bndrs, df_args = args }) _ (tidy_env', bndrs') = tidyBndrs tidy_env bndrs tidyUnfolding tidy_env - (CoreUnfolding { uf_tmpl = unf_rhs, uf_is_top = top_lvl - , uf_src = src, uf_guidance = guidance }) + unf@(CoreUnfolding { uf_tmpl = unf_rhs, uf_src = src }) unf_from_rhs | isStableSource src - = mkCoreUnfolding src top_lvl (tidyExpr tidy_env unf_rhs) guidance - -- Preserves OccInfo - - -- Note that uf_is_value and friends may be a thunk containing a reference - -- to the old template. Consequently it is important that we rebuild them, - -- despite the fact that they won't change, to avoid a space leak (since, - -- e.g., ToIface doesn't look at them; see #13564). This is the same - -- approach we use in Simplify.simplUnfolding and TcIface.tcUnfolding. + = seqIt $ unf { uf_tmpl = tidyExpr tidy_env unf_rhs } -- Preserves OccInfo + -- This seqIt avoids a space leak: otherwise the uf_is_value, + -- uf_is_conlike, ... fields may retain a reference to the + -- pre-tidied expression forever (ToIface doesn't look at them) | otherwise = unf_from_rhs + where seqIt unf = seqUnfolding unf `seq` unf tidyUnfolding _ unf _ = unf -- NoUnfolding or OtherCon {- diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index a5dd1ae..4ee88d1 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -744,7 +744,7 @@ test('T9020', test('T9675', [ only_ways(['optasm']), compiler_stats_num_field('max_bytes_used', # Note [residency] - [(wordsize(64), 25381032, 15), + [(wordsize(64), 17675240, 15), # 2014-10-13 29596552 # 2014-10-13 26570896 seq the DmdEnv in seqDmdType as well # 2014-10-13 18582472 different machines giving different results.. @@ -755,13 +755,12 @@ test('T9675', # 2016-03-14 38776008 Final demand analyzer run # 2016-04-01 29871032 Fix leaks in demand analysis # 2016-04-30 17675240 Fix leaks in tidy unfoldings - # 2017-05-08 25381032 CoreTidy: Don't seq unfoldings (wordsize(32), 18043224, 15) # 2015-07-11 15341228 (x86/Linux, 64-bit machine) use +RTS -G1 # 2016-04-06 18043224 (x86/Linux, 64-bit machine) ]), compiler_stats_num_field('peak_megabytes_allocated', # Note [residency] - [(wordsize(64), 94, 15), + [(wordsize(64), 63, 15), # 2014-10-13 66 # 2014-10-13 58 seq the DmdEnv in seqDmdType as well # 2014-10-13 49 different machines giving different results... @@ -773,7 +772,6 @@ test('T9675', # 2016-04-14 144 Final demand analyzer run # 2016-07-26 121 Unboxed sums? # 2017-04-30 63 Fix leaks in tidy unfoldings - # 2017-05-08 94 CoreTidy: Don't seq unfoldings (wordsize(32), 56, 15) # 2015-07-11 56 (x86/Linux, 64-bit machine) use +RTS -G1 ]), From git at git.haskell.org Wed May 10 08:02:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 May 2017 08:02:42 +0000 (UTC) Subject: [commit: ghc] master: Typos [ci skip] (22a03e7) Message-ID: <20170510080242.0929C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/22a03e7288129a165dc2cb866041185a06adb0e9/ghc >--------------------------------------------------------------- commit 22a03e7288129a165dc2cb866041185a06adb0e9 Author: Gabor Greif Date: Tue May 9 13:49:00 2017 +0200 Typos [ci skip] >--------------------------------------------------------------- 22a03e7288129a165dc2cb866041185a06adb0e9 compiler/basicTypes/MkId.hs | 2 +- compiler/main/SysTools.hs | 2 +- compiler/rename/RnBinds.hs | 2 +- compiler/rename/RnPat.hs | 2 +- compiler/specialise/SpecConstr.hs | 4 ++-- compiler/utils/Binary.hs | 4 ++-- rts/Schedule.c | 2 +- 7 files changed, 9 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/MkId.hs b/compiler/basicTypes/MkId.hs index 08b9efa..e9a57bc 100644 --- a/compiler/basicTypes/MkId.hs +++ b/compiler/basicTypes/MkId.hs @@ -1497,7 +1497,7 @@ Also see https://ghc.haskell.org/trac/ghc/wiki/OneShot. Note [magicDictId magic] ~~~~~~~~~~~~~~~~~~~~~~~~~ The identifier `magicDict` is just a place-holder, which is used to -implement a primitve that we cannot define in Haskell but we can write +implement a primitive that we cannot define in Haskell but we can write in Core. It is declared with a place-holder type: magicDict :: forall a. a diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs index ad2e33c..612206b 100644 --- a/compiler/main/SysTools.hs +++ b/compiler/main/SysTools.hs @@ -1508,7 +1508,7 @@ foreign import WINDOWS_CCONV unsafe "windows.h GetModuleFileNameW" -- is located at. See Trac #11759. getFinalPath :: FilePath -> IO (Maybe FilePath) getFinalPath name = do - dllHwnd <- failIfNull "LoadLibray" $ loadLibrary "kernel32.dll" + dllHwnd <- failIfNull "LoadLibrary" $ loadLibrary "kernel32.dll" -- Note: The API GetFinalPathNameByHandleW is only available starting from Windows Vista. -- This means that we can't bind directly to it since it may be missing. -- Instead try to find it's address at runtime and if we don't succeed consider the diff --git a/compiler/rename/RnBinds.hs b/compiler/rename/RnBinds.hs index 0b4cbeb..f91ca52 100644 --- a/compiler/rename/RnBinds.hs +++ b/compiler/rename/RnBinds.hs @@ -518,7 +518,7 @@ because they don't do anything! But we have two exceptions: (b) is sometimes used to give a type sig for, or an occurrence of, a variable on the RHS -* A strict patten binding; that is, one with an outermost bang +* A strict pattern binding; that is, one with an outermost bang !Just _ = e This can fail, so unlike the lazy variant, it is not a no-op. Moreover, Trac #13646 argues that even for single constructor diff --git a/compiler/rename/RnPat.hs b/compiler/rename/RnPat.hs index 77e2134..ac3cf64 100644 --- a/compiler/rename/RnPat.hs +++ b/compiler/rename/RnPat.hs @@ -432,7 +432,7 @@ rnPatAndThen mk (NPlusKPat rdr (L l lit) _ _ _ _) ; (lit', _) <- liftCpsFV $ rnOverLit lit -- See Note [Negative zero] -- We skip negateName as -- negative zero doesn't make - -- sense in n + k pattenrs + -- sense in n + k patterns ; minus <- liftCpsFV $ lookupSyntaxName minusName ; ge <- liftCpsFV $ lookupSyntaxName geName ; return (NPlusKPat (L (nameSrcSpan new_name) new_name) diff --git a/compiler/specialise/SpecConstr.hs b/compiler/specialise/SpecConstr.hs index dd6f191..39ec7e6 100644 --- a/compiler/specialise/SpecConstr.hs +++ b/compiler/specialise/SpecConstr.hs @@ -1952,8 +1952,8 @@ trim_pats env fn (SI { si_n_specs = done_spec_count }) pats -- segment of this list pat_cons :: CallPat -> Int - -- How many data consturorst of literals are in - -- the patten. More data-cons => less general + -- How many data constructors of literals are in + -- the pattern. More data-cons => less general pat_cons (qs, ps) = foldr ((+) . n_cons) 0 ps where q_set = mkVarSet qs diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index 9d385d2..99ab07e 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -336,7 +336,7 @@ getByte :: BinHandle -> IO Word8 getByte h = getWord8 h -- ----------------------------------------------------------------------------- --- Primitve Word writes +-- Primitive Word writes instance Binary Word8 where put_ = putWord8 @@ -355,7 +355,7 @@ instance Binary Word64 where get h = getWord64 h -- ----------------------------------------------------------------------------- --- Primitve Int writes +-- Primitive Int writes instance Binary Int8 where put_ h w = put_ h (fromIntegral w :: Word8) diff --git a/rts/Schedule.c b/rts/Schedule.c index 0a1d761..f82d924 100644 --- a/rts/Schedule.c +++ b/rts/Schedule.c @@ -2835,7 +2835,7 @@ deleteThread_(Capability *cap, StgTSO *tso) /* ----------------------------------------------------------------------------- raiseExceptionHelper - This function is called by the raise# primitve, just so that we can + This function is called by the raise# primitive, just so that we can move some of the tricky bits of raising an exception from C-- into C. Who knows, it might be a useful re-useable thing here too. -------------------------------------------------------------------------- */ From git at git.haskell.org Wed May 10 11:38:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 May 2017 11:38:04 +0000 (UTC) Subject: [commit: ghc] master: Efficient membership for home modules (26f509a) Message-ID: <20170510113804.80E4D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/26f509a992ebc6910ed2309b46f3f1d44efba7c9/ghc >--------------------------------------------------------------- commit 26f509a992ebc6910ed2309b46f3f1d44efba7c9 Author: Bartosz Nitka Date: Wed May 10 04:36:52 2017 -0700 Efficient membership for home modules This changes the linear lookup in a list to an efficient lookup in an IntMap. The linear lookup effectively made the algorithm quadratic, which for a test case that I have (5000 modules) introduced significant slowdown. I ran 3 experiments to estimate the impact of this: "No-op", profiled, just `:load`: P146, `186s` "before", profiled, `:load` followed by 10x `:r`: P147, `315s` "after", profiled, `:load` followed by 10x `:r`: P148, `250s` Going by the math of `(250-186)/(315-186) = 50%` this is a 2x improvement on `:r`. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Reviewed By: simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3562 >--------------------------------------------------------------- 26f509a992ebc6910ed2309b46f3f1d44efba7c9 compiler/main/GhcMake.hs | 12 +++++++----- 1 file changed, 7 insertions(+), 5 deletions(-) diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs index 7cc5276..4d06b6e 100644 --- a/compiler/main/GhcMake.hs +++ b/compiler/main/GhcMake.hs @@ -220,8 +220,9 @@ load' how_much mHscMessage mod_graph = do -- B.hs-boot in the module graph, but no B.hs -- The downsweep should have ensured this does not happen -- (see msDeps) - let all_home_mods = [ms_mod_name s - | s <- mod_graph, not (isBootSummary s)] + let all_home_mods = + mkUniqSet [ ms_mod_name s + | s <- mod_graph, not (isBootSummary s)] -- TODO: Figure out what the correct form of this assert is. It's violated -- when you have HsBootMerge nodes in the graph: then you'll have hs-boot -- files without corresponding hs files. @@ -236,7 +237,7 @@ load' how_much mHscMessage mod_graph = do checkHowMuch _ = id checkMod m and_then - | m `elem` all_home_mods = and_then + | m `elementOfUniqSet` all_home_mods = and_then | otherwise = do liftIO $ errorMsg dflags (text "no such module:" <+> quotes (ppr m)) @@ -656,7 +657,7 @@ unload hsc_env stable_linkables -- Unload everthing *except* 'stable_linkables' checkStability :: HomePackageTable -- HPT from last compilation -> [SCC ModSummary] -- current module graph (cyclic) - -> [ModuleName] -- all home modules + -> UniqSet ModuleName -- all home modules -> ([ModuleName], -- stableObject [ModuleName]) -- stableBCO @@ -669,7 +670,8 @@ checkStability hpt sccs all_home_mods = foldl checkSCC ([],[]) sccs where scc = flattenSCC scc0 scc_mods = map ms_mod_name scc - home_module m = m `elem` all_home_mods && m `notElem` scc_mods + home_module m = + m `elementOfUniqSet` all_home_mods && m `notElem` scc_mods scc_allimps = nub (filter home_module (concatMap ms_home_allimps scc)) -- all imports outside the current SCC, but in the home pkg From git at git.haskell.org Wed May 10 12:06:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 May 2017 12:06:22 +0000 (UTC) Subject: [commit: ghc] master: Fix a performance bug in GhcMake.downsweep (1893ba1) Message-ID: <20170510120622.A29AC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1893ba12fe1fa2ade35a62c336594afcd569736e/ghc >--------------------------------------------------------------- commit 1893ba12fe1fa2ade35a62c336594afcd569736e Author: Simon Marlow Date: Wed May 10 05:05:38 2017 -0700 Fix a performance bug in GhcMake.downsweep Every time we encountered a non-home module during the downsweep, we were removing it from the finder cache. That meant we were searching the filesystem for every import, rather than once per downsweep. The fix is just to flush the finder cache before the downsweep, and repopulate it for home modules that haven't changed. Speeds up downsweep by about 25% on a large example I have. Test Plan: Harbourmaster Reviewers: bgamari, niteria, austin, erikd Reviewed By: bgamari, niteria Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3554 >--------------------------------------------------------------- 1893ba12fe1fa2ade35a62c336594afcd569736e compiler/main/GhcMake.hs | 17 ++++++++++++----- 1 file changed, 12 insertions(+), 5 deletions(-) diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs index 4d06b6e..176c086 100644 --- a/compiler/main/GhcMake.hs +++ b/compiler/main/GhcMake.hs @@ -130,6 +130,12 @@ depanal excluded_mods allow_dup_roots = do text "Chasing modules from: ", hcat (punctuate comma (map pprTarget targets))]) + -- Home package modules may have been moved or deleted, and new + -- source files may have appeared in the home package that shadow + -- external package modules, so we have to discard the existing + -- cached finder data. + liftIO $ flushFinderCaches hsc_env + mod_graphE <- liftIO $ downsweep hsc_env old_graph excluded_mods allow_dup_roots mod_graph <- reportImportErrors mod_graphE @@ -1915,6 +1921,12 @@ summariseFile hsc_env old_summaries file mb_phase obj_allowed maybe_buf then liftIO $ getObjTimestamp location NotBoot else return Nothing hi_timestamp <- maybeGetIfaceDate dflags location + + -- We have to repopulate the Finder's cache because it + -- was flushed before the downsweep. + _ <- liftIO $ addHomeModuleToFinder hsc_env + (moduleName (ms_mod old_summary)) (ms_location old_summary) + return old_summary{ ms_obj_date = obj_timestamp , ms_iface_date = hi_timestamp } else @@ -2034,11 +2046,6 @@ summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod) new_summary location (ms_mod old_summary) src_fn src_timestamp find_it = do - -- Don't use the Finder's cache this time. If the module was - -- previously a package module, it may have now appeared on the - -- search path, so we want to consider it to be a home module. If - -- the module was previously a home module, it may have moved. - uncacheModule hsc_env wanted_mod found <- findImportedModule hsc_env wanted_mod Nothing case found of Found location mod From git at git.haskell.org Wed May 10 14:54:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 May 2017 14:54:14 +0000 (UTC) Subject: [commit: ghc] branch 'wip/cross-spec-constr' created Message-ID: <20170510145414.30C9E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/cross-spec-constr Referencing: 1b4c2095a07c6db66c854aa719a952940d3b04e2 From git at git.haskell.org Wed May 10 14:54:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 May 2017 14:54:19 +0000 (UTC) Subject: [commit: ghc] wip/cross-spec-constr: WIP: Make SpecConstr work across modules (1b4c209) Message-ID: <20170510145419.C3E5A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cross-spec-constr Link : http://ghc.haskell.org/trac/ghc/changeset/1b4c2095a07c6db66c854aa719a952940d3b04e2/ghc >--------------------------------------------------------------- commit 1b4c2095a07c6db66c854aa719a952940d3b04e2 Author: Matthew Pickering Date: Wed May 10 15:44:36 2017 +0100 WIP: Make SpecConstr work across modules Summary: This enables the SpecConst transformation to work across modules. I mostly copied and modified code from the normal specialiser and it seems to work. Here to validate and get feedback. TODO: []: Work out what SpecConstr actually does []: Add a test []: Clean up the mostly copied implementation Reviewers: simonpj, austin, bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #10346 Differential Revision: https://phabricator.haskell.org/D3566 >--------------------------------------------------------------- 1b4c2095a07c6db66c854aa719a952940d3b04e2 compiler/specialise/SpecConstr.hs | 67 +++++++++++++++++++++------------------ 1 file changed, 37 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 1b4c2095a07c6db66c854aa719a952940d3b04e2 From git at git.haskell.org Wed May 10 14:54:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 May 2017 14:54:17 +0000 (UTC) Subject: [commit: ghc] wip/cross-spec-constr: Working to the first degree (3db0ef2) Message-ID: <20170510145417.0AE1F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cross-spec-constr Link : http://ghc.haskell.org/trac/ghc/changeset/3db0ef28388ab95240babbc3a9e56de46f42b8c2/ghc >--------------------------------------------------------------- commit 3db0ef28388ab95240babbc3a9e56de46f42b8c2 Author: Matthew Pickering Date: Wed May 10 14:26:43 2017 +0100 Working to the first degree >--------------------------------------------------------------- 3db0ef28388ab95240babbc3a9e56de46f42b8c2 compiler/specialise/SpecConstr.hs | 232 +++++++++++++++++++++++++++++++------- compiler/specialise/Specialise.hs | 1 + 2 files changed, 190 insertions(+), 43 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 3db0ef28388ab95240babbc3a9e56de46f42b8c2 From git at git.haskell.org Wed May 10 18:22:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 May 2017 18:22:28 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Update allocations for T4801 on Darwin (4d9167b) Message-ID: <20170510182228.345A03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4d9167b087abd2f4dad4ccfaba7bbde177fd2797/ghc >--------------------------------------------------------------- commit 4d9167b087abd2f4dad4ccfaba7bbde177fd2797 Author: Ben Gamari Date: Wed May 10 13:02:41 2017 -0400 testsuite: Update allocations for T4801 on Darwin >--------------------------------------------------------------- 4d9167b087abd2f4dad4ccfaba7bbde177fd2797 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 4ee88d1..360bef4 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -240,9 +240,10 @@ test('T4801', # # 2014-10-13: 48 stricter seqDmdType compiler_stats_num_field('bytes allocated', - [(platform('x86_64-apple-darwin'), 465653312, 10), + [(platform('x86_64-apple-darwin'), 417302064, 10), # prev: 510938976 (amd64/OS X): # 2015-12-11: 465653312 (amd64/OS X) Update, bump tolerance to +/-10% + # 2017-03-24: 417302064 (amd64/OS X) Correlated with Linux improvement (wordsize(32), 199856388, 10), # prev: 185669232 (x86/OSX) From git at git.haskell.org Thu May 11 02:53:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 02:53:42 +0000 (UTC) Subject: [commit: ghc] master: mailmap: Add Douglas Wilson (63ba812) Message-ID: <20170511025342.9E61F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/63ba81262a5a73ccef5ea18e0e40679e141ee28f/ghc >--------------------------------------------------------------- commit 63ba81262a5a73ccef5ea18e0e40679e141ee28f Author: Ben Gamari Date: Wed May 10 22:51:25 2017 -0400 mailmap: Add Douglas Wilson >--------------------------------------------------------------- 63ba81262a5a73ccef5ea18e0e40679e141ee28f .mailmap | 1 + 1 file changed, 1 insertion(+) diff --git a/.mailmap b/.mailmap index cdfcf0e..60d746d 100644 --- a/.mailmap +++ b/.mailmap @@ -93,6 +93,7 @@ Don Stewart dons Don Stewart dons at cse.unsw.edu.au Don Syme dsyme +Douglas Wilson doug Donnie Jones donnie at darthik.com Duncan Coutts Duncan Coutts From git at git.haskell.org Thu May 11 11:55:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 11:55:38 +0000 (UTC) Subject: [commit: ghc] wip/cross-spec-constr: Remove traces (39c8a56) Message-ID: <20170511115538.ADDCD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cross-spec-constr Link : http://ghc.haskell.org/trac/ghc/changeset/39c8a5625564dd4e92ce1d01decc9691970913a8/ghc >--------------------------------------------------------------- commit 39c8a5625564dd4e92ce1d01decc9691970913a8 Author: Matthew Pickering Date: Thu May 11 11:41:17 2017 +0100 Remove traces >--------------------------------------------------------------- 39c8a5625564dd4e92ce1d01decc9691970913a8 compiler/specialise/SpecConstr.hs | 32 +++++++++++++++----------------- compiler/specialise/Specialise.hs | 2 +- 2 files changed, 16 insertions(+), 18 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 39c8a5625564dd4e92ce1d01decc9691970913a8 From git at git.haskell.org Thu May 11 13:00:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 13:00:51 +0000 (UTC) Subject: [commit: ghc] master: libffi via submodule (8d4bce4) Message-ID: <20170511130051.846523A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8d4bce42de7929b0dec7e7d68e66bcfc4d266322/ghc >--------------------------------------------------------------- commit 8d4bce42de7929b0dec7e7d68e66bcfc4d266322 Author: Moritz Angermann Date: Thu May 11 18:11:12 2017 +0800 libffi via submodule This is rather annoying. I'd prefer to have a stable release to use. However libffi-3.2.1 has been released November 12, 2014, and libffi-4 is TBD. See also https://github.com/libffi/libffi/issues/296 The core reason for this change is that llvm changed the supported assembly to unified syntax, which libffi-3.2.1 does not use, and hence fails to compile for arm with llvm. For refence, see the following issue: https://github.com/libffi/libffi/issues/191 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, snowleopard Differential Revision: https://phabricator.haskell.org/D3349 >--------------------------------------------------------------- 8d4bce42de7929b0dec7e7d68e66bcfc4d266322 .gitmodules | 7 +++---- libffi-tarballs | 1 - libffi/build | 1 + libffi/ghc.mk | 9 ++++----- packages | 2 +- 5 files changed, 9 insertions(+), 11 deletions(-) diff --git a/.gitmodules b/.gitmodules index 55d360a..a1af41c 100644 --- a/.gitmodules +++ b/.gitmodules @@ -111,13 +111,12 @@ path = utils/hsc2hs url = ../hsc2hs.git ignore = none -[submodule "libffi-tarballs"] - path = libffi-tarballs - url = ../libffi-tarballs.git - ignore = none [submodule "gmp-tarballs"] path = libraries/integer-gmp/gmp/gmp-tarballs url = ../gmp-tarballs.git [submodule ".arc-linters/arcanist-external-json-linter"] path = .arc-linters/arcanist-external-json-linter url = ../arcanist-external-json-linter.git +[submodule "libffi/build"] + path = libffi/build + url = https://github.com/libffi/libffi.git diff --git a/libffi-tarballs b/libffi-tarballs deleted file mode 160000 index ec37a68..0000000 --- a/libffi-tarballs +++ /dev/null @@ -1 +0,0 @@ -Subproject commit ec37a68838566cb830c33cb30bfade003a306cff diff --git a/libffi/build b/libffi/build new file mode 160000 index 0000000..b841ae7 --- /dev/null +++ b/libffi/build @@ -0,0 +1 @@ +Subproject commit b841ae70a05a5e11de1fca1b4551189db0895cf2 diff --git a/libffi/ghc.mk b/libffi/ghc.mk index 7c5bc9e..08f5e4d 100644 --- a/libffi/ghc.mk +++ b/libffi/ghc.mk @@ -50,9 +50,8 @@ $(libffi_STAMP_CONFIGURE): $(TOUCH_DEP) $(call removeFiles,$(libffi_STAMP_STATIC_SHARED_CONFIGURE)) $(call removeFiles,$(libffi_STAMP_STATIC_SHARED_BUILD)) $(call removeFiles,$(libffi_STAMP_STATIC_SHARED_INSTALL)) - $(call removeTrees,$(LIBFFI_DIR) libffi/build) - cat libffi-tarballs/libffi*.tar.gz | $(GZIP_CMD) -d | { cd libffi && $(TAR_CMD) -xf - ; } - mv libffi/libffi-* libffi/build + git clean -x -f -d libffi/build + cd libffi/build && ./autogen.sh # update config.guess/config.sub $(CP) "$(TOP)/config.guess" libffi/build/config.guess @@ -123,10 +122,10 @@ $(libffi_STATIC_LIB): $(libffi_STAMP_INSTALL) @test -f $@ || { echo "$< exists, but $@ does not."; echo "Suggest removing $<."; exit 1; } $(libffi_HEADERS): $(libffi_STAMP_INSTALL) | $$(dir $$@)/. - cp -f libffi/build/inst/lib/libffi-*/include/$(notdir $@) $@ + cp -f libffi/build/inst/include/$(notdir $@) $@ $(eval $(call clean-target,libffi,, \ - libffi/build $(wildcard libffi/stamp.ffi.*) libffi/dist-install)) + $(wildcard libffi/stamp.ffi.*) libffi/dist-install)) endif diff --git a/packages b/packages index a99bac6..6efcfb3 100644 --- a/packages +++ b/packages @@ -38,7 +38,7 @@ # localpath tag remotepath upstreamurl # ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ghc-tarballs windows ghc-tarballs.git - -libffi-tarballs - - - +libffi/build - - https://github.com/libffi/libffi.git utils/hsc2hs - - - utils/haddock - - ssh://git at github.com/haskell/haddock.git libraries/array - - - From git at git.haskell.org Thu May 11 13:00:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 13:00:56 +0000 (UTC) Subject: [commit: ghc] master: [iserv] fix loadDLL (83dcaa8) Message-ID: <20170511130056.E85CB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/83dcaa8c1e25e5d73c0010029ade30713c0e1696/ghc >--------------------------------------------------------------- commit 83dcaa8c1e25e5d73c0010029ade30713c0e1696 Author: Moritz Angermann Date: Thu May 11 18:13:28 2017 +0800 [iserv] fix loadDLL When we load non absolute pathed .so's this usually implies that we expect the system to have them in place already, and hence we should not need to ship them. Without the absolute path to the library, we are also unable to open and send said library. Thus we'll do library shipping only for libraries with absolute paths. Reviewers: austin, bgamari, simonmar Reviewed By: simonmar Subscribers: simonmar, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3469 >--------------------------------------------------------------- 83dcaa8c1e25e5d73c0010029ade30713c0e1696 iserv/iserv-bin.cabal | 2 ++ iserv/proxy-src/Remote.hs | 8 +++++++- iserv/src/Remote/Slave.hs | 41 ++++++++++++++++++++++++++++++----------- 3 files changed, 39 insertions(+), 12 deletions(-) diff --git a/iserv/iserv-bin.cabal b/iserv/iserv-bin.cabal index 8da0c28..846a111 100644 --- a/iserv/iserv-bin.cabal +++ b/iserv/iserv-bin.cabal @@ -134,5 +134,7 @@ Executable iserv-proxy containers >= 0.5 && < 0.6, deepseq >= 1.4 && < 1.5, ghci == 8.3, + directory >= 1.3 && < 1.4, network >= 2.6, + filepath >= 1.4 && < 1.5, iserv-bin diff --git a/iserv/proxy-src/Remote.hs b/iserv/proxy-src/Remote.hs index 481d6ac..c91b2d0 100644 --- a/iserv/proxy-src/Remote.hs +++ b/iserv/proxy-src/Remote.hs @@ -59,6 +59,8 @@ import System.Environment import System.Exit import Text.Printf import GHC.Fingerprint (getFileHash) +import System.Directory +import System.FilePath (isAbsolute) import Data.Binary import qualified Data.ByteString as BS @@ -68,7 +70,7 @@ dieWithUsage = do prog <- getProgName die $ prog ++ ": " ++ msg where -#ifdef WINDOWS +#if defined(WINDOWS) msg = "usage: iserv [-v]" #else msg = "usage: iserv [-v]" @@ -231,6 +233,10 @@ proxy verbose local remote = loop resp <- fwdLoadCall verbose local remote msg' reply resp loop + LoadDLL path | isAbsolute path -> do + resp <- fwdLoadCall verbose local remote msg' + reply resp + loop Shutdown{} -> fwdCall msg' >> return () _other -> fwdCall msg' >>= reply >> loop diff --git a/iserv/src/Remote/Slave.hs b/iserv/src/Remote/Slave.hs index e7ff3f2..c7210dc 100644 --- a/iserv/src/Remote/Slave.hs +++ b/iserv/src/Remote/Slave.hs @@ -11,7 +11,9 @@ import Control.Exception import Control.Concurrent import Control.Monad (when, forever) import System.Directory -import System.FilePath (takeDirectory) +import System.FilePath (takeDirectory, (), dropTrailingPathSeparator, + isAbsolute, joinPath, splitPath) +import GHCi.ResolvedBCO import Data.IORef import GHCi.Message (Pipe(..), Msg(..), Message(..), readPipe, writePipe) @@ -23,6 +25,17 @@ import GHC.Fingerprint (getFileHash) import qualified Data.ByteString as BS + +dropLeadingPathSeparator :: FilePath -> FilePath +dropLeadingPathSeparator p | isAbsolute p = joinPath (drop 1 (splitPath p)) + | otherwise = p + +-- | Path concatication that prevents a double path separator to appear in the +-- final path. "/foo/bar/" "/baz/quux" == "/foo/bar/baz/quux" +() :: FilePath -> FilePath -> FilePath +lhs rhs = dropTrailingPathSeparator lhs dropLeadingPathSeparator rhs +infixr 5 + foreign export ccall startSlave :: Bool -> Int -> CString -> IO () -- | @startSlave@ is the exported slave function, that the @@ -89,18 +102,24 @@ handleLoad pipe path localPath = do hook :: Bool -> String -> Pipe -> Msg -> IO Msg hook verbose base_path pipe m = case m of Msg (AddLibrarySearchPath p) -> do - when verbose $ putStrLn ("Need Path: " ++ base_path ++ p) - createDirectoryIfMissing True (base_path ++ p) - return $ Msg (AddLibrarySearchPath (base_path ++ p)) + when verbose $ putStrLn ("Need Path: " ++ (base_path p)) + createDirectoryIfMissing True (base_path p) + return $ Msg (AddLibrarySearchPath (base_path p)) Msg (LoadObj path) -> do - handleLoad pipe path (base_path ++ path) - return $ Msg (LoadObj (base_path ++ path)) + when verbose $ putStrLn ("Need Obj: " ++ (base_path path)) + handleLoad pipe path (base_path path) + return $ Msg (LoadObj (base_path path)) Msg (LoadArchive path) -> do - handleLoad pipe path (base_path ++ path) - return $ Msg (LoadArchive (base_path ++ path)) - -- Msg (LoadDLL path) -> do - -- handleLoad ctl_pipe path (base_path ++ path) - -- return $ Msg (LoadDLL (base_path ++ path)) + handleLoad pipe path (base_path path) + return $ Msg (LoadArchive (base_path path)) + -- when loading DLLs (.so, .dylib, .dll, ...) and these are provided + -- as relative paths, the intention is to load a pre-existing system library, + -- therefore we hook the LoadDLL call only for absolute paths to ship the + -- dll from the host to the target. + Msg (LoadDLL path) | isAbsolute path -> do + when verbose $ putStrLn ("Need DLL: " ++ (base_path path)) + handleLoad pipe path (base_path path) + return $ Msg (LoadDLL (base_path path)) _other -> return m -------------------------------------------------------------------------------- From git at git.haskell.org Thu May 11 13:00:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 13:00:59 +0000 (UTC) Subject: [commit: ghc] master: We define the `_HOST_ARCH` to `1`, but never to `0`in (b5ca082) Message-ID: <20170511130059.BFEA03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b5ca082d297bc6306f445cb672a07b907dff8b18/ghc >--------------------------------------------------------------- commit b5ca082d297bc6306f445cb672a07b907dff8b18 Author: Moritz Angermann Date: Thu May 11 18:14:26 2017 +0800 We define the `_HOST_ARCH` to `1`, but never to `0`in compiler/ghc.mk @echo "#define $(HostArch_CPP)_HOST_ARCH 1" >> $@ @echo "#define $(TargetArch_CPP)_HOST_ARCH 1" >> $@ this leads to warnigns like: > warning: 'x86_64_HOST_ARCH' is not defined, evaluates to 0 [-Wundef] Reviewers: austin, bgamari, erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3555 >--------------------------------------------------------------- b5ca082d297bc6306f445cb672a07b907dff8b18 rts/linker/MachOTypes.h | 7 ++++--- rts/sm/HeapAlloc.h | 2 +- rts/win32/OSThreads.c | 16 ++++++++-------- 3 files changed, 13 insertions(+), 12 deletions(-) diff --git a/rts/linker/MachOTypes.h b/rts/linker/MachOTypes.h index 7d9d64c..4176c48 100644 --- a/rts/linker/MachOTypes.h +++ b/rts/linker/MachOTypes.h @@ -6,13 +6,14 @@ #include -#if x86_64_HOST_ARCH || powerpc64_HOST_ARCH \ - || aarch64_HOST_ARCH || arm64_HOST_ARCH +#if defined(x86_64_HOST_ARCH) || defined(powerpc64_HOST_ARCH) \ + || defined(aarch64_HOST_ARCH) || defined(arm64_HOST_ARCH) typedef struct mach_header_64 MachOHeader; typedef struct segment_command_64 MachOSegmentCommand; typedef struct section_64 MachOSection; typedef struct nlist_64 MachONList; -#elif i386_HOST_ARCH || powerpc_HOST_ARCH || arm_HOST_ARCH +#elif defined(i386_HOST_ARCH) || defined(powerpc_HOST_ARCH) \ + || defined(arm_HOST_ARCH) typedef struct mach_header MachOHeader; typedef struct segment_command MachOSegmentCommand; typedef struct section MachOSection; diff --git a/rts/sm/HeapAlloc.h b/rts/sm/HeapAlloc.h index 9a36d10..197317f 100644 --- a/rts/sm/HeapAlloc.h +++ b/rts/sm/HeapAlloc.h @@ -130,7 +130,7 @@ extern StgWord8 mblock_map[]; #define MBC_LINE_BITS 0 #define MBC_TAG_BITS 15 -#if x86_64_HOST_ARCH +#if defined(x86_64_HOST_ARCH) // 32bits are enough for 'entry' as modern amd64 boxes have // only 48bit sized virtual addres. typedef StgWord32 MbcCacheLine; diff --git a/rts/win32/OSThreads.c b/rts/win32/OSThreads.c index 4deb14a..ad42340 100644 --- a/rts/win32/OSThreads.c +++ b/rts/win32/OSThreads.c @@ -251,7 +251,7 @@ forkOS_createThread ( HsStablePtr entry ) (unsigned*)&pId) == 0); } -#if x86_64_HOST_ARCH +#if defined(x86_64_HOST_ARCH) /* We still support Windows Vista, so we can't depend on it and must manually resolve these. */ typedef DWORD(WINAPI *GetItemCountProc)(WORD); @@ -306,7 +306,7 @@ getNumberOfProcessorsGroups (void) static uint8_t n_groups = 0; -#if x86_64_HOST_ARCH +#if defined(x86_64_HOST_ARCH) if (!n_groups) { /* We still support Windows Vista. Which means we can't rely @@ -328,7 +328,7 @@ getNumberOfProcessorsGroups (void) return n_groups; } -#if x86_64_HOST_ARCH +#if defined(x86_64_HOST_ARCH) static uint8_t* getProcessorsDistribution (void) { @@ -377,7 +377,7 @@ getProcessorsCumulativeSum(void) cpuGroupCumulativeCache = malloc(n_groups * sizeof(uint32_t)); memset(cpuGroupCumulativeCache, 0, n_groups * sizeof(uint32_t)); -#if x86_64_HOST_ARCH +#if defined(x86_64_HOST_ARCH) uint8_t* proc_dist = getProcessorsDistribution(); uint32_t cum_num_proc = 0; for (int i = 0; i < n_groups; i++) @@ -419,7 +419,7 @@ createProcessorGroupMap (void) /* For 32bit Windows and 64bit older than Windows 7, create a default mapping. */ memset(cpuGroupCache, 0, numProcs * sizeof(uint8_t)); -#if x86_64_HOST_ARCH +#if defined(x86_64_HOST_ARCH) uint8_t* proc_dist = getProcessorsDistribution(); int totalProcs = 0; @@ -443,7 +443,7 @@ getNumberOfProcessors (void) { static uint32_t nproc = 0; -#if x86_64_HOST_ARCH +#if defined(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"); @@ -510,7 +510,7 @@ setThreadAffinity (uint32_t n, uint32_t m) // cap N of M mask[group] |= 1 << ix; } -#if x86_64_HOST_ARCH +#if defined(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"); @@ -520,7 +520,7 @@ setThreadAffinity (uint32_t n, uint32_t m) // cap N of M for (i = 0; i < n_groups; i++) { -#if x86_64_HOST_ARCH +#if defined(x86_64_HOST_ARCH) // If we support the new API, use it. if (mask[i] > 0 && SetThreadGroupAffinity) { From git at git.haskell.org Thu May 11 13:00:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 13:00:54 +0000 (UTC) Subject: [commit: ghc] master: Do not hardcode the specific linker to use (5ddb307) Message-ID: <20170511130054.3BD8E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5ddb307edf15c4d86e5c35c4063ec967424e19f2/ghc >--------------------------------------------------------------- commit 5ddb307edf15c4d86e5c35c4063ec967424e19f2 Author: Moritz Angermann Date: Thu May 11 18:12:33 2017 +0800 Do not hardcode the specific linker to use This should be handled appropriately by a wrapper script around the compiler, if one wants to insist on the specific linker to be used. Otherwise this breaks if the used compiler fails to understand this directive. I believe that using a specific linker should be part of the compilers toolchain, we delegate to and not hardcoded here in ghc. Reviewers: dfeuer, erikd, hvr, austin, rwbarton, bgamari Reviewed By: bgamari Subscribers: snowleopard, davean, dfeuer, thomie, erikd Differential Revision: https://phabricator.haskell.org/D3351 >--------------------------------------------------------------- 5ddb307edf15c4d86e5c35c4063ec967424e19f2 aclocal.m4 | 37 ++++++++++++++++++++++++++----------- configure.ac | 2 +- distrib/configure.ac.in | 2 +- 3 files changed, 28 insertions(+), 13 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index d874d41..32e55cd 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -572,6 +572,7 @@ AC_DEFUN([FP_SET_CFLAGS_C99], # $5 is the name of the CPP flags variable AC_DEFUN([FPTOOLS_SET_C_LD_FLAGS], [ + FIND_LD([$1],[UseLd]) AC_MSG_CHECKING([Setting up $2, $3, $4 and $5]) case $$1 in i386-*) @@ -610,18 +611,14 @@ AC_DEFUN([FPTOOLS_SET_C_LD_FLAGS], ;; arm*linux*) # On arm/linux and arm/android, tell gcc to generate Arm - # instructions (ie not Thumb) and to link using the gold linker. - # Forcing LD to be ld.gold is done in FIND_LD m4 macro. + # instructions (ie not Thumb). $2="$$2 -marm" - $3="$$3 -fuse-ld=gold -Wl,-z,noexecstack" + $3="$$3 -Wl,-z,noexecstack" $4="$$4 -z noexecstack" ;; aarch64*linux*) - # On aarch64/linux and aarch64/android, tell gcc to link using the - # gold linker. - # Forcing LD to be ld.gold is done in FIND_LD m4 macro. - $3="$$3 -fuse-ld=gold -Wl,-z,noexecstack" + $3="$$3 -Wl,-z,noexecstack" $4="$$4 -z noexecstack" ;; @@ -642,6 +639,15 @@ AC_DEFUN([FPTOOLS_SET_C_LD_FLAGS], esac + case $UseLd in + *ld.gold) + $3="$$3 -fuse-ld=gold" + ;; + *ld.bfd) + $3="$$3 -fuse-ld=bfd" + ;; + esac + # If gcc knows about the stack protector, turn it off. # Otherwise the stack-smash handler gets triggered. echo 'int main(void) {return 0;}' > conftest.c @@ -1991,11 +1997,12 @@ AC_DEFUN([FIND_LLVM_PROG],[ # Find the version of `ld` to use. This is used in both in the top level # configure.ac and in distrib/configure.ac.in. # -# $1 = the variable to set +# $1 = the platform +# $2 = the variable to set # AC_DEFUN([FIND_LD],[ AC_CHECK_TARGET_TOOL([LD], [ld]) - case $target in + case $1 in arm*linux* | \ aarch64*linux* ) # Arm and Aarch64 requires use of the binutils ld.gold linker. @@ -2003,10 +2010,18 @@ AC_DEFUN([FIND_LD],[ # arm-linux-androideabi, arm64-unknown-linux and # aarch64-linux-android AC_CHECK_TARGET_TOOL([LD_GOLD], [ld.gold]) - $1="$LD_GOLD" + if test "$LD_GOLD" != ""; then + $2="$LD_GOLD" + elif test `$LD --version | grep -c "GNU gold"` -gt 0; then + AC_MSG_NOTICE([ld is ld.gold]) + $2="$LD" + else + AC_MSG_WARN([could not find ld.gold, falling back to $LD]) + $2="$LD" + fi ;; *) - $1="$LD" + $2="$LD" ;; esac ]) diff --git a/configure.ac b/configure.ac index 0a0f790..73ee64d 100644 --- a/configure.ac +++ b/configure.ac @@ -497,7 +497,7 @@ FP_SET_CFLAGS_C99([CC],[CONF_CC_OPTS_STAGE2],[CONF_CPP_OPTS_STAGE2]) dnl ** Which ld to use? dnl -------------------------------------------------------------- -FIND_LD([LdCmd]) +FIND_LD([$target],[LdCmd]) AC_SUBST([LdCmd]) dnl ** Which nm to use? diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index ffa0574..cea3c49 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -86,7 +86,7 @@ AC_SUBST([OptCmd]) dnl ** Which ld to use? dnl -------------------------------------------------------------- -FIND_LD([LdCmd]) +FIND_LD([$target],[LdCmd]) AC_SUBST([LdCmd]) FP_GCC_VERSION From git at git.haskell.org Thu May 11 13:01:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 13:01:02 +0000 (UTC) Subject: [commit: ghc] master: bump config.{guess,sub} (418bcf7) Message-ID: <20170511130102.8280F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/418bcf736cc8d861f338e09f278091ba3657644f/ghc >--------------------------------------------------------------- commit 418bcf736cc8d861f338e09f278091ba3657644f Author: Moritz Angermann Date: Thu May 11 18:15:46 2017 +0800 bump config.{guess,sub} There is no new autoconf release, and it seems like there will unlikely be one . This will allow us to support -apple-ios properly. These have been taken from - http://git.savannah.gnu.org/gitweb/?p=config.git;a=blob_plain;f=config.guess - http://git.savannah.gnu.org/gitweb/?p=config.git;a=blob_plain;f=config.sub Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3558 >--------------------------------------------------------------- 418bcf736cc8d861f338e09f278091ba3657644f config.guess | 184 +++++++++++++++++++++++-------------- config.sub | 90 +++++++++++++----- libraries/base/config.guess | 184 +++++++++++++++++++++++-------------- libraries/base/config.sub | 90 +++++++++++++----- libraries/integer-gmp/config.guess | 184 +++++++++++++++++++++++-------------- libraries/integer-gmp/config.sub | 90 +++++++++++++----- 6 files changed, 543 insertions(+), 279 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 418bcf736cc8d861f338e09f278091ba3657644f From git at git.haskell.org Thu May 11 13:01:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 13:01:05 +0000 (UTC) Subject: [commit: ghc] master: Pass LLVMTarget (identical to --target) (1345c7c) Message-ID: <20170511130105.39C753A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1345c7cc42c45e63ab1726a8fd24a7e4d4222467/ghc >--------------------------------------------------------------- commit 1345c7cc42c45e63ab1726a8fd24a7e4d4222467 Author: Moritz Angermann Date: Thu May 11 18:17:02 2017 +0800 Pass LLVMTarget (identical to --target) Sometimes it might be of interest to have access to the raw target value when calling subcommands (e.g. llvm tools with --target), as such we forward the specified (or inferred) --target for later consumption. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, erikd Differential Revision: https://phabricator.haskell.org/D3559 >--------------------------------------------------------------- 1345c7cc42c45e63ab1726a8fd24a7e4d4222467 aclocal.m4 | 5 +++++ compiler/ghc.mk | 2 ++ mk/project.mk.in | 37 +++++++++++++++++++------------------ 3 files changed, 26 insertions(+), 18 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 0d113c1..a7920a7 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -136,9 +136,13 @@ AC_DEFUN([FPTOOLS_SET_PLATFORM_VARS], TargetVendor_CPP=` echo "$TargetVendor" | sed -e 's/\./_/g' -e 's/-/_/g'` TargetOS_CPP=` echo "$TargetOS" | sed -e 's/\./_/g' -e 's/-/_/g'` + # we intend to pass trough --targets to llvm as is. + LLVMTarget_CPP=` echo "$target"` + echo "GHC build : $BuildPlatform" echo "GHC host : $HostPlatform" echo "GHC target : $TargetPlatform" + echo "LLVM target: $target" AC_SUBST(BuildPlatform) AC_SUBST(HostPlatform) @@ -154,6 +158,7 @@ AC_DEFUN([FPTOOLS_SET_PLATFORM_VARS], AC_SUBST(HostOS_CPP) AC_SUBST(BuildOS_CPP) AC_SUBST(TargetOS_CPP) + AC_SUBST(LLVMTarget_CPP) AC_SUBST(HostVendor_CPP) AC_SUBST(BuildVendor_CPP) diff --git a/compiler/ghc.mk b/compiler/ghc.mk index d5498c4..2d2fede 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -170,6 +170,7 @@ compiler/stage1/$(PLATFORM_H) : mk/config.mk mk/project.mk | $$(dir $$@)/. @echo "#define BUILD_ARCH \"$(BuildArch_CPP)\"" >> $@ @echo "#define HOST_ARCH \"$(HostArch_CPP)\"" >> $@ @echo "#define TARGET_ARCH \"$(TargetArch_CPP)\"" >> $@ + @echo "#define LLVM_TARGET \"$(LLVMTarget_CPP)\"" >> $@ @echo >> $@ @echo "#define $(BuildOS_CPP)_BUILD_OS 1" >> $@ @echo "#define $(HostOS_CPP)_HOST_OS 1" >> $@ @@ -211,6 +212,7 @@ compiler/stage2/$(PLATFORM_H) : mk/config.mk mk/project.mk | $$(dir $$@)/. @echo "#define BUILD_ARCH \"$(HostArch_CPP)\"" >> $@ @echo "#define HOST_ARCH \"$(TargetArch_CPP)\"" >> $@ @echo "#define TARGET_ARCH \"$(TargetArch_CPP)\"" >> $@ + @echo "#define LLVM_TARGET \"$(LLVMTarget_CPP)\"" >> $@ @echo >> $@ @echo "#define $(HostOS_CPP)_BUILD_OS 1" >> $@ @echo "#define $(TargetOS_CPP)_HOST_OS 1" >> $@ diff --git a/mk/project.mk.in b/mk/project.mk.in index 03bd744..d620ed5 100644 --- a/mk/project.mk.in +++ b/mk/project.mk.in @@ -12,7 +12,7 @@ # Versioning scheme: A.B.C # A: major version, decimal, any number of digits # B: minor version, decimal, any number of digits -# C: patchlevel, one digit, omitted if zero. +# C: patchlevel, one digit, omitted if zero. # # ProjectVersionInt does *not* contain the patchlevel (rationale: this # figure is used for conditional compilations, and library interfaces @@ -35,7 +35,7 @@ ProjectGitCommitId = @ProjectGitCommitId@ ################################################################################ # -# Platform variables +# Platform variables # ################################################################################ @@ -81,24 +81,25 @@ ProjectGitCommitId = @ProjectGitCommitId@ # You have to do a lot of work by hand to cross compile: see the # section on "Porting GHC" in the Building Guide. -HOSTPLATFORM = @HostPlatform@ -TARGETPLATFORM = @TargetPlatform@ -BUILDPLATFORM = @BuildPlatform@ +HOSTPLATFORM = @HostPlatform@ +TARGETPLATFORM = @TargetPlatform@ +BUILDPLATFORM = @BuildPlatform@ -HostPlatform_CPP = @HostPlatform_CPP@ -HostArch_CPP = @HostArch_CPP@ -HostOS_CPP = @HostOS_CPP@ -HostVendor_CPP = @HostVendor_CPP@ +HostPlatform_CPP = @HostPlatform_CPP@ +HostArch_CPP = @HostArch_CPP@ +HostOS_CPP = @HostOS_CPP@ +HostVendor_CPP = @HostVendor_CPP@ -TargetPlatform_CPP = @TargetPlatform_CPP@ -TargetArch_CPP = @TargetArch_CPP@ -TargetOS_CPP = @TargetOS_CPP@ -TargetVendor_CPP = @TargetVendor_CPP@ +TargetPlatform_CPP = @TargetPlatform_CPP@ +TargetArch_CPP = @TargetArch_CPP@ +TargetOS_CPP = @TargetOS_CPP@ +TargetVendor_CPP = @TargetVendor_CPP@ +LLVMTarget_CPP = @LLVMTarget_CPP@ -BuildPlatform_CPP = @BuildPlatform_CPP@ -BuildArch_CPP = @BuildArch_CPP@ -BuildOS_CPP = @BuildOS_CPP@ -BuildVendor_CPP = @BuildVendor_CPP@ +BuildPlatform_CPP = @BuildPlatform_CPP@ +BuildArch_CPP = @BuildArch_CPP@ +BuildOS_CPP = @BuildOS_CPP@ +BuildVendor_CPP = @BuildVendor_CPP@ @HostPlatform_CPP at _HOST = 1 @TargetPlatform_CPP at _TARGET = 1 @@ -118,7 +119,7 @@ BuildVendor_CPP = @BuildVendor_CPP@ ################################################################################ # -# Global configuration options +# Global configuration options # ################################################################################ From git at git.haskell.org Thu May 11 13:01:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 13:01:07 +0000 (UTC) Subject: [commit: ghc] master: Fix iossimulator (094a752) Message-ID: <20170511130107.EB7D63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/094a752a1561b5cb8640648b0882cea97831226c/ghc >--------------------------------------------------------------- commit 094a752a1561b5cb8640648b0882cea97831226c Author: Moritz Angermann Date: Thu May 11 18:14:47 2017 +0800 Fix iossimulator The introduction of the aarch64 linker for iOS forgot that the ios simulator was still using the x86_64/mach-o linker, which requires the use of symbol extras. Until this is overhauled (see #13678), we should revert to the symbol extras logic for x86_64-apple-ios Reviewers: austin, bgamari, erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3556 >--------------------------------------------------------------- 094a752a1561b5cb8640648b0882cea97831226c rts/LinkerInternals.h | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/rts/LinkerInternals.h b/rts/LinkerInternals.h index a884561..b8c411d 100644 --- a/rts/LinkerInternals.h +++ b/rts/LinkerInternals.h @@ -109,6 +109,11 @@ typedef struct ForeignExportStablePtr_ { #endif /* ios_HOST_OS */ #endif +/* iOS Simulator however, needs symbol extras for now (#13678) */ +#if defined(ios_HOST_OS) && defined(x86_64_HOST_ARCH) +#define NEED_SYMBOL_EXTRAS 1 +#endif + /* Jump Islands are sniplets of machine code required for relative * address relocations on the PowerPC, x86_64 and ARM. */ From git at git.haskell.org Thu May 11 13:01:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 13:01:10 +0000 (UTC) Subject: [commit: ghc] master: Drop custom apple handling (6ef6e7c) Message-ID: <20170511130110.A05303A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6ef6e7c6a74729a6a6bae4f9ba39e216ad13ac70/ghc >--------------------------------------------------------------- commit 6ef6e7c6a74729a6a6bae4f9ba39e216ad13ac70 Author: Moritz Angermann Date: Thu May 11 18:15:22 2017 +0800 Drop custom apple handling We know that *-apple-* is leading_underscores, and .dylib. It is also better to test for TargetVendor being apple, rather than relying on targetOS, which could be macOS, iOS, tvOS, watchOS, or any other glorious name apple could come up with. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, erikd Differential Revision: https://phabricator.haskell.org/D3557 >--------------------------------------------------------------- 6ef6e7c6a74729a6a6bae4f9ba39e216ad13ac70 aclocal.m4 | 50 +++++++++++++++++++------------------------------- 1 file changed, 19 insertions(+), 31 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 32e55cd..0d113c1 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -20,14 +20,8 @@ AC_DEFUN([GHC_SELECT_FILE_EXTENSIONS], $2='.exe' $3='.dll' ;; - i386-apple-darwin|powerpc-apple-darwin) - $3='.dylib' - ;; - x86_64-apple-darwin) - $3='.dylib' - ;; - arm-apple-darwin10|i386-apple-darwin11|aarch64-apple-darwin14|x86_64-apple-darwin14) - $2='.a' + # apple platform uses .dylib (macOS, iOS, ...) + *-apple-*) $3='.dylib' ;; esac @@ -796,20 +790,17 @@ AC_CACHE_CHECK([leading underscore in symbol names], [fptools_cv_leading_undersc # Hack!: nlist() under Digital UNIX insist on there being an _, # but symbol table listings shows none. What is going on here?!? case $TargetPlatform in -*linux-android*) fptools_cv_leading_underscore=no;; -*openbsd*) # x86 openbsd is ELF from 3.4 >, meaning no leading uscore - case $build in - i386-*2\.@<:@0-9@:>@ | i386-*3\.@<:@0-3@:>@ ) fptools_cv_leading_underscore=yes ;; - *) fptools_cv_leading_underscore=no ;; - esac ;; -i386-unknown-mingw32) fptools_cv_leading_underscore=yes;; -x86_64-unknown-mingw32) fptools_cv_leading_underscore=no;; - - # HACK: Apple doesn't seem to provide nlist in the 64-bit-libraries -x86_64-apple-darwin*) fptools_cv_leading_underscore=yes;; -*-apple-ios) fptools_cv_leading_underscore=yes;; - -*) AC_RUN_IFELSE([AC_LANG_SOURCE([[#ifdef HAVE_NLIST_H + # Apples mach-o platforms use leading underscores + *-apple-*) fptools_cv_leading_underscore=yes;; + *linux-android*) fptools_cv_leading_underscore=no;; + *openbsd*) # x86 openbsd is ELF from 3.4 >, meaning no leading uscore + case $build in + i386-*2\.@<:@0-9@:>@ | i386-*3\.@<:@0-3@:>@ ) fptools_cv_leading_underscore=yes ;; + *) fptools_cv_leading_underscore=no ;; + esac ;; + i386-unknown-mingw32) fptools_cv_leading_underscore=yes;; + x86_64-unknown-mingw32) fptools_cv_leading_underscore=no;; + *) AC_RUN_IFELSE([AC_LANG_SOURCE([[#ifdef HAVE_NLIST_H #include struct nlist xYzzY1[] = {{"xYzzY1", 0},{0}}; struct nlist xYzzY2[] = {{"_xYzzY2", 0},{0}}; @@ -1145,7 +1136,7 @@ AC_DEFUN([FP_PROG_AR_NEEDS_RANLIB],[ if test $fp_prog_ar_is_gnu = yes then fp_cv_prog_ar_needs_ranlib=no - elif test "$TargetOS_CPP" = "darwin" + elif test "$TargetVendor_CPP" = "apple" then # It's quite tedious to check for Apple's crazy timestamps in # .a files, so we hardcode it. @@ -1882,12 +1873,11 @@ AC_DEFUN([GHC_CONVERT_VENDOR],[ # -------------------------------- # converts os from gnu to ghc naming, and assigns the result to $target_var AC_DEFUN([GHC_CONVERT_OS],[ -case "$1-$2" in - darwin10-arm|darwin11-i386|darwin14-aarch64|darwin14-x86_64) - $3="ios" - ;; - *) case "$1" in + # watchos and tvos are ios variant as of May 2017. + ios|watchos|tvos) + $3="ios" + ;; linux-android*) $3="linux-android" ;; @@ -1914,8 +1904,6 @@ case "$1-$2" in exit 1 ;; esac - ;; - esac ]) # BOOTSTRAPPING_GHC_INFO_FIELD @@ -1947,7 +1935,7 @@ AC_SUBST(LIBRARY_[]translit([$1], [-], [_])[]_VERSION) # -------------------------------- # Gets the version number of XCode, if on a Mac AC_DEFUN([XCODE_VERSION],[ - if test "$TargetOS_CPP" = "darwin" + if test "$TargetVendor_CPP" = "apple" then AC_MSG_CHECKING(XCode version) XCodeVersion=`xcodebuild -version | grep Xcode | sed "s/Xcode //"` From git at git.haskell.org Thu May 11 13:01:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 13:01:13 +0000 (UTC) Subject: [commit: ghc] master: Use NEED_PTHREAD_LIB (c0872bf) Message-ID: <20170511130113.5A51E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c0872bf99ff891e440f118bf9eea20b980c2cfca/ghc >--------------------------------------------------------------- commit c0872bf99ff891e440f118bf9eea20b980c2cfca Author: Moritz Angermann Date: Thu May 11 18:17:31 2017 +0800 Use NEED_PTHREAD_LIB we do the same for the rts already. And using the configure script should be more robust than hand-picking the OSs here. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3563 >--------------------------------------------------------------- c0872bf99ff891e440f118bf9eea20b980c2cfca compiler/main/DriverPipeline.hs | 19 ++++++++----------- 1 file changed, 8 insertions(+), 11 deletions(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 474fd8c..07e5edd 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1887,22 +1887,19 @@ linkBinary' staticLink dflags o_files dep_packages = do -- Here are some libs that need to be linked at the *end* of -- the command line, because they contain symbols that are referred to -- by the RTS. We can't therefore use the ordinary way opts for these. - let - debug_opts | WayDebug `elem` ways dflags = [ + let debug_opts | WayDebug `elem` ways dflags = [ #if defined(HAVE_LIBBFD) "-lbfd", "-liberty" #endif ] - | otherwise = [] + | otherwise = [] - let thread_opts - | WayThreaded `elem` ways dflags = - let os = platformOS (targetPlatform dflags) - in if os `elem` [OSMinGW32, OSFreeBSD, OSOpenBSD, OSAndroid, - OSNetBSD, OSHaiku, OSQNXNTO, OSiOS, OSDarwin] - then [] - else ["-lpthread"] - | otherwise = [] + thread_opts | WayThreaded `elem` ways dflags = [ +#if NEED_PTHREAD_LIB + "-lpthread" +#endif + ] + | otherwise = [] rc_objs <- maybeCreateManifest dflags output_fn From git at git.haskell.org Thu May 11 13:13:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 13:13:22 +0000 (UTC) Subject: [commit: ghc] master: Revert "libffi via submodule" (a67cfc7) Message-ID: <20170511131322.CB5503A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a67cfc790256884be9ce784b1439556308db3c53/ghc >--------------------------------------------------------------- commit a67cfc790256884be9ce784b1439556308db3c53 Author: Moritz Angermann Date: Thu May 11 21:12:34 2017 +0800 Revert "libffi via submodule" This reverts commit 8d4bce42de7929b0dec7e7d68e66bcfc4d266322. >--------------------------------------------------------------- a67cfc790256884be9ce784b1439556308db3c53 .gitmodules | 7 ++++--- libffi-tarballs | 1 + libffi/build | 1 - libffi/ghc.mk | 9 +++++---- packages | 2 +- 5 files changed, 11 insertions(+), 9 deletions(-) diff --git a/.gitmodules b/.gitmodules index a1af41c..55d360a 100644 --- a/.gitmodules +++ b/.gitmodules @@ -111,12 +111,13 @@ path = utils/hsc2hs url = ../hsc2hs.git ignore = none +[submodule "libffi-tarballs"] + path = libffi-tarballs + url = ../libffi-tarballs.git + ignore = none [submodule "gmp-tarballs"] path = libraries/integer-gmp/gmp/gmp-tarballs url = ../gmp-tarballs.git [submodule ".arc-linters/arcanist-external-json-linter"] path = .arc-linters/arcanist-external-json-linter url = ../arcanist-external-json-linter.git -[submodule "libffi/build"] - path = libffi/build - url = https://github.com/libffi/libffi.git diff --git a/libffi-tarballs b/libffi-tarballs new file mode 160000 index 0000000..ec37a68 --- /dev/null +++ b/libffi-tarballs @@ -0,0 +1 @@ +Subproject commit ec37a68838566cb830c33cb30bfade003a306cff diff --git a/libffi/build b/libffi/build deleted file mode 160000 index b841ae7..0000000 --- a/libffi/build +++ /dev/null @@ -1 +0,0 @@ -Subproject commit b841ae70a05a5e11de1fca1b4551189db0895cf2 diff --git a/libffi/ghc.mk b/libffi/ghc.mk index 08f5e4d..7c5bc9e 100644 --- a/libffi/ghc.mk +++ b/libffi/ghc.mk @@ -50,8 +50,9 @@ $(libffi_STAMP_CONFIGURE): $(TOUCH_DEP) $(call removeFiles,$(libffi_STAMP_STATIC_SHARED_CONFIGURE)) $(call removeFiles,$(libffi_STAMP_STATIC_SHARED_BUILD)) $(call removeFiles,$(libffi_STAMP_STATIC_SHARED_INSTALL)) - git clean -x -f -d libffi/build - cd libffi/build && ./autogen.sh + $(call removeTrees,$(LIBFFI_DIR) libffi/build) + cat libffi-tarballs/libffi*.tar.gz | $(GZIP_CMD) -d | { cd libffi && $(TAR_CMD) -xf - ; } + mv libffi/libffi-* libffi/build # update config.guess/config.sub $(CP) "$(TOP)/config.guess" libffi/build/config.guess @@ -122,10 +123,10 @@ $(libffi_STATIC_LIB): $(libffi_STAMP_INSTALL) @test -f $@ || { echo "$< exists, but $@ does not."; echo "Suggest removing $<."; exit 1; } $(libffi_HEADERS): $(libffi_STAMP_INSTALL) | $$(dir $$@)/. - cp -f libffi/build/inst/include/$(notdir $@) $@ + cp -f libffi/build/inst/lib/libffi-*/include/$(notdir $@) $@ $(eval $(call clean-target,libffi,, \ - $(wildcard libffi/stamp.ffi.*) libffi/dist-install)) + libffi/build $(wildcard libffi/stamp.ffi.*) libffi/dist-install)) endif diff --git a/packages b/packages index 6efcfb3..a99bac6 100644 --- a/packages +++ b/packages @@ -38,7 +38,7 @@ # localpath tag remotepath upstreamurl # ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ghc-tarballs windows ghc-tarballs.git - -libffi/build - - https://github.com/libffi/libffi.git +libffi-tarballs - - - utils/hsc2hs - - - utils/haddock - - ssh://git at github.com/haskell/haddock.git libraries/array - - - From git at git.haskell.org Thu May 11 13:36:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 13:36:13 +0000 (UTC) Subject: [commit: ghc] master: Add regression test for #12850 (2316ee1) Message-ID: <20170511133613.08C213A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2316ee1c42d7f4dc229295a5b5426dde40944dc1/ghc >--------------------------------------------------------------- commit 2316ee1c42d7f4dc229295a5b5426dde40944dc1 Author: Ryan Scott Date: Thu May 11 09:33:43 2017 -0400 Add regression test for #12850 Commit e7985ed23ddc68b6a2e4af753578dc1d9e8ab4c9 happened to fix #12850, so let's add a regression test for the program reported in #12850. >--------------------------------------------------------------- 2316ee1c42d7f4dc229295a5b5426dde40944dc1 testsuite/tests/typecheck/should_compile/T12850.hs | 10 ++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 11 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T12850.hs b/testsuite/tests/typecheck/should_compile/T12850.hs new file mode 100644 index 0000000..660b4c5 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T12850.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE ExplicitForAll, MagicHash, KindSignatures #-} +module T12850 where + +import GHC.Types (RuntimeRep(..), TYPE) + +f :: forall (x :: TYPE 'IntRep). x -> x +f x = x + +g = () + where h = f 0# diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 6db86a8..2f34144 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -530,6 +530,7 @@ test('T12734a', normal, compile_fail, ['']) test('T12763', normal, compile, ['']) test('T12785a', normal, compile, ['']) test('T12797', normal, compile, ['']) +test('T12850', normal, compile, ['']) test('T12911', normal, compile, ['']) test('T12925', normal, compile, ['']) test('T12919', expect_broken(12919), compile, ['']) From git at git.haskell.org Thu May 11 21:33:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 21:33:28 +0000 (UTC) Subject: [commit: ghc] master: pmCheck: Don't generate PmId OccNames from Uniques (6f99923) Message-ID: <20170511213328.967963A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6f999230e8f955ee61c470d34a02650165643f68/ghc >--------------------------------------------------------------- commit 6f999230e8f955ee61c470d34a02650165643f68 Author: Ben Gamari Date: Thu May 11 00:17:04 2017 -0400 pmCheck: Don't generate PmId OccNames from Uniques Doug Wilson astutely noticed that the pattern match checker was spending a significant amount of time in mkPmId. It turns out that it was producing Ids with OccNames that were generated from a Unique, which are non-trivial to render. Since Var is strict in Name, Name in OccName, and OccName in its FastString all of this encoding work was being done despite the fact that it was (as far as I can tell) never actually needed. Test Plan: Validate, note allocations of `T11195` Reviewers: austin, gkaracha Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3568 >--------------------------------------------------------------- 6f999230e8f955ee61c470d34a02650165643f68 compiler/deSugar/Check.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index da1f004..3215856 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -1038,7 +1038,7 @@ mkPmVars tys = mapM mkPmVar tys -- | Generate a fresh `Id` of a given type mkPmId :: Type -> DsM Id mkPmId ty = getUniqueM >>= \unique -> - let occname = mkVarOccFS (fsLit (show unique)) + let occname = mkVarOccFS $ fsLit "$pm" name = mkInternalName unique occname noSrcSpan in return (mkLocalId name ty) From git at git.haskell.org Thu May 11 21:33:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 21:33:32 +0000 (UTC) Subject: [commit: ghc] master: Fix incorrect ambiguity error on identically-named data constructors (1381c14) Message-ID: <20170511213332.2E4EE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1381c142cd8d030f9997cdc206dcad006c028bbb/ghc >--------------------------------------------------------------- commit 1381c142cd8d030f9997cdc206dcad006c028bbb Author: Soham Chowdhury Date: Thu May 11 15:40:18 2017 -0400 Fix incorrect ambiguity error on identically-named data constructors Given multiple in-scope constructors with the same name, say `A`, and a function of type `A -> Int`, say, the compiler reports both a "type `A` is not in scope" and (incorrectly) an ambiguity error. The latter shouldn't be there if `DataKinds` isn't enabled. This issue was recommended to me by @mpickering as a suitable first task, and the fix was also outlined in the original Trac ticket. It involved a simple reordering of the steps taken in `lookup_demoted` in `RnEnv.hs`. The fix is to make the `DataKinds` check happen earlier, ensuring that the ambiguity check doesn't happen at all if we know the constructors couldn't have been promoted. Signed-off-by: Soham Chowdhury Reviewers: mpickering, austin, bgamari Reviewed By: mpickering, bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13568 Differential Revision: https://phabricator.haskell.org/D3547 >--------------------------------------------------------------- 1381c142cd8d030f9997cdc206dcad006c028bbb compiler/rename/RnEnv.hs | 21 +++++++++++---------- testsuite/tests/module/mod122.stderr | 4 +++- testsuite/tests/module/mod123.stderr | 4 +++- testsuite/tests/module/mod124.stderr | 1 + testsuite/tests/module/mod127.stderr | 1 + testsuite/tests/module/mod29.stderr | 1 + testsuite/tests/module/mod50.stderr | 4 +++- .../tests/parser/should_fail/readFail001.stderr | 1 + .../tests/rename/prog003/rename.prog003.stderr | 4 +++- testsuite/tests/rename/should_fail/T13568.hs | 8 ++++++++ testsuite/tests/rename/should_fail/T13568.stderr | 4 ++++ testsuite/tests/rename/should_fail/T13568a.hs | 3 +++ testsuite/tests/rename/should_fail/T1595a.stderr | 4 +++- testsuite/tests/rename/should_fail/T5745.stderr | 4 +++- testsuite/tests/rename/should_fail/all.T | 1 + testsuite/tests/typecheck/should_fail/T1595.stderr | 6 ++++-- .../tests/typecheck/should_fail/tcfail048.stderr | 4 +++- .../tests/typecheck/should_fail/tcfail053.stderr | 4 +++- 18 files changed, 59 insertions(+), 20 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 1381c142cd8d030f9997cdc206dcad006c028bbb From git at git.haskell.org Thu May 11 21:33:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 21:33:34 +0000 (UTC) Subject: [commit: ghc] master: compiler: Do not look up fail in RnExpr if bind pattern is irrefutible. (2fcb5c5) Message-ID: <20170511213334.DB36C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2fcb5c5c3f6c5a5936eeb5dc07b476e5737f12ad/ghc >--------------------------------------------------------------- commit 2fcb5c5c3f6c5a5936eeb5dc07b476e5737f12ad Author: Aaron Friel Date: Thu May 11 15:41:22 2017 -0400 compiler: Do not look up fail in RnExpr if bind pattern is irrefutible. Adds a check in `rnStmt`, in sub-expr `getFailFunction`, to determine if the pattern of a bind statement is irrefutible. If so, skip looking up the `fail` name. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13649 Differential Revision: https://phabricator.haskell.org/D3553 >--------------------------------------------------------------- 2fcb5c5c3f6c5a5936eeb5dc07b476e5737f12ad compiler/rename/RnExpr.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/compiler/rename/RnExpr.hs b/compiler/rename/RnExpr.hs index 154e270..ce22784 100644 --- a/compiler/rename/RnExpr.hs +++ b/compiler/rename/RnExpr.hs @@ -833,6 +833,10 @@ rnStmt ctxt rnBody (L loc (BindStmt pat body _ _ _)) thing_inside ; xMonadFailEnabled <- fmap (xopt LangExt.MonadFailDesugaring) getDynFlags ; let getFailFunction + -- If the pattern is irrefutible (e.g.: wildcard, tuple, + -- ~pat, etc.) we should not need to fail. + | isIrrefutableHsPat pat + = return (noSyntaxExpr, emptyFVs) -- For non-monadic contexts (e.g. guard patterns, list -- comprehensions, etc.) we should not need to fail. -- See Note [Failing pattern matches in Stmts] From git at git.haskell.org Thu May 11 21:33:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 21:33:37 +0000 (UTC) Subject: [commit: ghc] master: rts: Don't build StgCRunAsm.S if unregisterised (aa8dcb3) Message-ID: <20170511213337.9D2C23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/aa8dcb33fd26d8bfd4cac2fbd1b1785b4a869897/ghc >--------------------------------------------------------------- commit aa8dcb33fd26d8bfd4cac2fbd1b1785b4a869897 Author: Ben Gamari Date: Thu May 11 15:41:38 2017 -0400 rts: Don't build StgCRunAsm.S if unregisterised StgCRunAsm.S provides StgCRun on powerpc64le platforms when registerised. However, in the unregisterised setting we use the mini-interpreter and consequently shouldn't build StgCRunAsm.S lest we get duplicate symbols. Test Plan: Build unregisterised compiler on AIX. Reviewers: hvr, trommler, austin, simonmar Reviewed By: trommler, simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3560 >--------------------------------------------------------------- aa8dcb33fd26d8bfd4cac2fbd1b1785b4a869897 rts/ghc.mk | 3 +++ 1 file changed, 3 insertions(+) diff --git a/rts/ghc.mk b/rts/ghc.mk index d089859..990f4db 100644 --- a/rts/ghc.mk +++ b/rts/ghc.mk @@ -55,9 +55,12 @@ rts_S_SRCS += rts/AdjustorAsm.S endif # this matches substrings of powerpc64le, including "powerpc" and "powerpc64" ifneq "$(findstring $(TargetArch_CPP), powerpc64le)" "" +# unregisterised builds use the mini interpreter +ifneq "$(GhcUnregisterised)" "YES" rts_S_SRCS += rts/StgCRunAsm.S endif endif +endif ifeq "$(GhcUnregisterised)" "YES" GENAPPLY_OPTS = -u From git at git.haskell.org Thu May 11 21:33:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 21:33:40 +0000 (UTC) Subject: [commit: ghc] master: Add Outputable instance for Node (6e890e8) Message-ID: <20170511213340.5E4833A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6e890e8c9b960805c87268e9b3ce2e3d4a58297b/ghc >--------------------------------------------------------------- commit 6e890e8c9b960805c87268e9b3ce2e3d4a58297b Author: Matthew Pickering Date: Thu May 11 15:42:02 2017 -0400 Add Outputable instance for Node Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3564 >--------------------------------------------------------------- 6e890e8c9b960805c87268e9b3ce2e3d4a58297b compiler/utils/Digraph.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/compiler/utils/Digraph.hs b/compiler/utils/Digraph.hs index fe325e6..e3b5037 100644 --- a/compiler/utils/Digraph.hs +++ b/compiler/utils/Digraph.hs @@ -99,6 +99,9 @@ data Node key payload = DigraphNode { -- it's ok to have extra keys in the dependencies that -- are not the key of any Node in the graph +instance (Outputable a, Outputable b) => Outputable (Node a b) where + ppr (DigraphNode a b c) = ppr (a, b, c) + emptyGraph :: Graph a emptyGraph = Graph (array (1, 0) []) (error "emptyGraph") (const Nothing) From git at git.haskell.org Thu May 11 21:33:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 21:33:43 +0000 (UTC) Subject: [commit: ghc] master: Parenthesize pretty-printed equalities when necessary (2277172) Message-ID: <20170511213343.A1B733A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2277172ac3ea0bbeddebc9999a5d8b5f9f58afc9/ghc >--------------------------------------------------------------- commit 2277172ac3ea0bbeddebc9999a5d8b5f9f58afc9 Author: Ryan Scott Date: Thu May 11 15:42:55 2017 -0400 Parenthesize pretty-printed equalities when necessary Fixes #13677 by parenthesizing equalities in a sufficiently high pretty-printing context. Test Plan: make test TEST=T13677 Reviewers: goldfire, austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13677 Differential Revision: https://phabricator.haskell.org/D3570 >--------------------------------------------------------------- 2277172ac3ea0bbeddebc9999a5d8b5f9f58afc9 compiler/iface/IfaceType.hs | 2 +- testsuite/tests/typecheck/should_fail/T13677.hs | 11 +++++++++++ testsuite/tests/typecheck/should_fail/T13677.stderr | 4 ++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 4 files changed, 17 insertions(+), 1 deletion(-) diff --git a/compiler/iface/IfaceType.hs b/compiler/iface/IfaceType.hs index 41cf4f6..eafd6dd 100644 --- a/compiler/iface/IfaceType.hs +++ b/compiler/iface/IfaceType.hs @@ -979,7 +979,7 @@ pprTyTcApp' ctxt_prec tc tys dflags style -> text "(TypeError ...)" | Just doc <- ppr_equality tc (tcArgsIfaceTypes tys) - -> doc + -> maybeParen ctxt_prec TyConPrec doc | otherwise -> ppr_iface_tc_app ppr_ty ctxt_prec tc tys_wo_kinds diff --git a/testsuite/tests/typecheck/should_fail/T13677.hs b/testsuite/tests/typecheck/should_fail/T13677.hs new file mode 100644 index 0000000..f452a20 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T13677.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE ConstraintKinds #-} +{-# LANGUAGE GADTs #-} +module T13677 where + +import GHC.Exts (Constraint) + +data Dict a where + Dict :: a => Dict a + +foo :: Dict (Int ~ Int) => Int +foo = undefined diff --git a/testsuite/tests/typecheck/should_fail/T13677.stderr b/testsuite/tests/typecheck/should_fail/T13677.stderr new file mode 100644 index 0000000..c29aba2 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T13677.stderr @@ -0,0 +1,4 @@ + +T13677.hs:10:8: error: + • Expected a constraint, but ‘Dict (Int ~ Int)’ has kind ‘*’ + • In the type signature: foo :: Dict (Int ~ Int) => Int diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 4a409e0..3875063 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -438,3 +438,4 @@ test('T13506', normal, compile_fail, ['']) test('T13611', expect_broken(13611), compile_fail, ['']) test('T13320', normal, compile_fail, ['']) test('T13640', normal, compile_fail, ['']) +test('T13677', normal, compile_fail, ['']) From git at git.haskell.org Thu May 11 21:33:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 21:33:46 +0000 (UTC) Subject: [commit: ghc] master: Use Proxy rather than undefined in MatchLit (1f770a5) Message-ID: <20170511213346.5AB853A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1f770a521e2331ce01007d36490d3b206afc6b4b/ghc >--------------------------------------------------------------- commit 1f770a521e2331ce01007d36490d3b206afc6b4b Author: Matthew Pickering Date: Thu May 11 15:42:23 2017 -0400 Use Proxy rather than undefined in MatchLit Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3565 >--------------------------------------------------------------- 1f770a521e2331ce01007d36490d3b206afc6b4b compiler/deSugar/MatchLit.hs | 47 ++++++++++++++++++++++---------------------- 1 file changed, 24 insertions(+), 23 deletions(-) diff --git a/compiler/deSugar/MatchLit.hs b/compiler/deSugar/MatchLit.hs index e04e618..748de5c 100644 --- a/compiler/deSugar/MatchLit.hs +++ b/compiler/deSugar/MatchLit.hs @@ -49,6 +49,7 @@ import qualified GHC.LanguageExtensions as LangExt import Control.Monad import Data.Int import Data.Word +import Data.Proxy {- ************************************************************************ @@ -156,21 +157,21 @@ warnAboutOverflowedLiterals :: DynFlags -> HsOverLit Id -> DsM () warnAboutOverflowedLiterals dflags lit | wopt Opt_WarnOverflowedLiterals dflags , Just (i, tc) <- getIntegralLit lit - = if tc == intTyConName then check i tc (undefined :: Int) - else if tc == int8TyConName then check i tc (undefined :: Int8) - else if tc == int16TyConName then check i tc (undefined :: Int16) - else if tc == int32TyConName then check i tc (undefined :: Int32) - else if tc == int64TyConName then check i tc (undefined :: Int64) - else if tc == wordTyConName then check i tc (undefined :: Word) - else if tc == word8TyConName then check i tc (undefined :: Word8) - else if tc == word16TyConName then check i tc (undefined :: Word16) - else if tc == word32TyConName then check i tc (undefined :: Word32) - else if tc == word64TyConName then check i tc (undefined :: Word64) + = if tc == intTyConName then check i tc (Proxy :: Proxy Int) + else if tc == int8TyConName then check i tc (Proxy :: Proxy Int8) + else if tc == int16TyConName then check i tc (Proxy :: Proxy Int16) + else if tc == int32TyConName then check i tc (Proxy :: Proxy Int32) + else if tc == int64TyConName then check i tc (Proxy :: Proxy Int64) + else if tc == wordTyConName then check i tc (Proxy :: Proxy Word) + else if tc == word8TyConName then check i tc (Proxy :: Proxy Word8) + else if tc == word16TyConName then check i tc (Proxy :: Proxy Word16) + else if tc == word32TyConName then check i tc (Proxy :: Proxy Word32) + else if tc == word64TyConName then check i tc (Proxy :: Proxy Word64) else return () | otherwise = return () where - check :: forall a. (Bounded a, Integral a) => Integer -> Name -> a -> DsM () + check :: forall a. (Bounded a, Integral a) => Integer -> Name -> Proxy a -> DsM () check i tc _proxy = when (i < minB || i > maxB) $ do warnDs (Reason Opt_WarnOverflowedLiterals) @@ -207,7 +208,7 @@ warnAboutEmptyEnumerations dflags fromExpr mThnExpr toExpr , Just (from,tc) <- getLHsIntegralLit fromExpr , Just mThn <- traverse getLHsIntegralLit mThnExpr , Just (to,_) <- getLHsIntegralLit toExpr - , let check :: forall a. (Enum a, Num a) => a -> DsM () + , let check :: forall a. (Enum a, Num a) => Proxy a -> DsM () check _proxy = when (null enumeration) $ warnDs (Reason Opt_WarnEmptyEnumerations) (text "Enumeration is empty") @@ -217,17 +218,17 @@ warnAboutEmptyEnumerations dflags fromExpr mThnExpr toExpr Nothing -> [fromInteger from .. fromInteger to] Just (thn,_) -> [fromInteger from, fromInteger thn .. fromInteger to] - = if tc == intTyConName then check (undefined :: Int) - else if tc == int8TyConName then check (undefined :: Int8) - else if tc == int16TyConName then check (undefined :: Int16) - else if tc == int32TyConName then check (undefined :: Int32) - else if tc == int64TyConName then check (undefined :: Int64) - else if tc == wordTyConName then check (undefined :: Word) - else if tc == word8TyConName then check (undefined :: Word8) - else if tc == word16TyConName then check (undefined :: Word16) - else if tc == word32TyConName then check (undefined :: Word32) - else if tc == word64TyConName then check (undefined :: Word64) - else if tc == integerTyConName then check (undefined :: Integer) + = if tc == intTyConName then check (Proxy :: Proxy Int) + else if tc == int8TyConName then check (Proxy :: Proxy Int8) + else if tc == int16TyConName then check (Proxy :: Proxy Int16) + else if tc == int32TyConName then check (Proxy :: Proxy Int32) + else if tc == int64TyConName then check (Proxy :: Proxy Int64) + else if tc == wordTyConName then check (Proxy :: Proxy Word) + else if tc == word8TyConName then check (Proxy :: Proxy Word8) + else if tc == word16TyConName then check (Proxy :: Proxy Word16) + else if tc == word32TyConName then check (Proxy :: Proxy Word32) + else if tc == word64TyConName then check (Proxy :: Proxy Word64) + else if tc == integerTyConName then check (Proxy :: Proxy Integer) else return () | otherwise = return () From git at git.haskell.org Thu May 11 21:33:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 21:33:49 +0000 (UTC) Subject: [commit: ghc] master: Fix collect_lpat's treatment of HsSplicedPats (eaf9cc4) Message-ID: <20170511213349.ADBAF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eaf9cc4240019c2e91922ef38ae7236b59d59bdd/ghc >--------------------------------------------------------------- commit eaf9cc4240019c2e91922ef38ae7236b59d59bdd Author: Ryan Scott Date: Thu May 11 15:46:02 2017 -0400 Fix collect_lpat's treatment of HsSplicedPats `collect_lpat` was missing a case for `HsSplicedPat`, which caused incorrect renaming of TH-spliced pattern variables. Fixes #13473. Test Plan: make test TEST=T13473 Reviewers: facundominguez, austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13473 Differential Revision: https://phabricator.haskell.org/D3572 >--------------------------------------------------------------- eaf9cc4240019c2e91922ef38ae7236b59d59bdd compiler/hsSyn/HsUtils.hs | 3 +++ testsuite/tests/th/T13473.hs | 13 +++++++++++++ .../{deSugar/should_run/T13285.stdout => th/T13473.stdout} | 0 testsuite/tests/th/T13473a.hs | 10 ++++++++++ testsuite/tests/th/all.T | 2 ++ 5 files changed, 28 insertions(+) diff --git a/compiler/hsSyn/HsUtils.hs b/compiler/hsSyn/HsUtils.hs index 2b3a5c6..a15aa15 100644 --- a/compiler/hsSyn/HsUtils.hs +++ b/compiler/hsSyn/HsUtils.hs @@ -965,6 +965,9 @@ collect_lpat (L _ pat) bndrs go (SigPatIn pat _) = collect_lpat pat bndrs go (SigPatOut pat _) = collect_lpat pat bndrs + + go (SplicePat (HsSpliced _ (HsSplicedPat pat))) + = go pat go (SplicePat _) = bndrs go (CoPat _ pat _) = go pat diff --git a/testsuite/tests/th/T13473.hs b/testsuite/tests/th/T13473.hs new file mode 100644 index 0000000..d977626 --- /dev/null +++ b/testsuite/tests/th/T13473.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE QuasiQuotes #-} +{-# LANGUAGE TemplateHaskell #-} +module Main where + +import Language.Haskell.TH +import T13473a + +[quoter|y|] = 1 + +main :: IO () +main = do + let $(varP $ mkName "x") = 1 in print x + print y diff --git a/testsuite/tests/deSugar/should_run/T13285.stdout b/testsuite/tests/th/T13473.stdout similarity index 100% copy from testsuite/tests/deSugar/should_run/T13285.stdout copy to testsuite/tests/th/T13473.stdout diff --git a/testsuite/tests/th/T13473a.hs b/testsuite/tests/th/T13473a.hs new file mode 100644 index 0000000..fcd6ebb --- /dev/null +++ b/testsuite/tests/th/T13473a.hs @@ -0,0 +1,10 @@ +module T13473a where + +import Language.Haskell.TH +import Language.Haskell.TH.Quote + +quoter :: QuasiQuoter +quoter = QuasiQuoter { quotePat = varP . mkName + , quoteExp = undefined + , quoteDec = undefined + , quoteType = undefined } diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index fd4530a..40e3b17 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -381,6 +381,8 @@ test('T13123', normal, compile, ['-v0']) test('T13098', normal, compile, ['-v0']) test('T11046', normal, multimod_compile, ['T11046','-v0']) test('T13366', normal, compile_and_run, ['-lstdc++ -v0']) +test('T13473', normal, multimod_compile_and_run, + ['T13473.hs', '-v0 ' + config.ghc_th_way_flags]) test('T13587', expect_broken(13587), compile_and_run, ['-v0']) test('T13618', normal, compile_and_run, ['-v0']) test('T13642', normal, compile_fail, ['-v0']) From git at git.haskell.org Thu May 11 21:33:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 21:33:53 +0000 (UTC) Subject: [commit: ghc] master: Allow spliced patterns in pattern synonyms (01db135) Message-ID: <20170511213353.36F443A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/01db13586a6eab9f66101b01d1b0584f334d5d25/ghc >--------------------------------------------------------------- commit 01db13586a6eab9f66101b01d1b0584f334d5d25 Author: Ben Gamari Date: Thu May 11 15:46:37 2017 -0400 Allow spliced patterns in pattern synonyms This ended up being quite simple. Reviewers: austin, goldfire, mpickering Subscribers: rwbarton, shlevy, thomie GHC Trac Issues: #13688 Differential Revision: https://phabricator.haskell.org/D3571 >--------------------------------------------------------------- 01db13586a6eab9f66101b01d1b0584f334d5d25 compiler/typecheck/TcPatSyn.hs | 15 ++++++++------- testsuite/tests/patsyn/should_run/T13688.hs | 21 +++++++++++++++++++++ testsuite/tests/patsyn/should_run/T13688.stdout | 4 ++++ testsuite/tests/patsyn/should_run/T13688Quasi.hs | 12 ++++++++++++ testsuite/tests/patsyn/should_run/all.T | 1 + 5 files changed, 46 insertions(+), 7 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index 97bafa5..4b4b042 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -667,6 +667,9 @@ tcPatToExpr args pat = go pat go1 (ConPatOut{}) = panic "ConPatOut in output of renamer" go1 (SigPatOut{}) = panic "SigPatOut in output of renamer" go1 (CoPat{}) = panic "CoPat in output of renamer" + go1 (SplicePat (HsSpliced _ (HsSplicedPat pat))) + = go1 pat + go1 (SplicePat (HsSpliced{})) = panic "Invalid splice variety" go1 p = Left (text "pattern" <+> quotes (ppr p) <+> text "is not invertible") {- Note [Builder for a bidirectional pattern synonym] @@ -771,7 +774,11 @@ tcCheckPatSynPat = go go1 NPat{} = return () go1 (SigPatIn pat _) = go pat go1 (ViewPat _ pat _) = go pat - go1 p at SplicePat{} = thInPatSynErr p + go1 (SplicePat splice) + | HsSpliced mod_finalizers (HsSplicedPat pat) <- splice + = do addModFinalizersWithLclEnv mod_finalizers + go1 pat + | otherwise = panic "non-pattern from spliced thing" go1 p at NPlusKPat{} = nPlusKPatInPatSynErr p go1 ConPatOut{} = panic "ConPatOut in output of renamer" go1 SigPatOut{} = panic "SigPatOut in output of renamer" @@ -783,12 +790,6 @@ asPatInPatSynErr pat hang (text "Pattern synonym definition cannot contain as-patterns (@):") 2 (ppr pat) -thInPatSynErr :: (OutputableBndrId name) => Pat name -> TcM a -thInPatSynErr pat - = failWithTc $ - hang (text "Pattern synonym definition cannot contain Template Haskell:") - 2 (ppr pat) - nPlusKPatInPatSynErr :: (OutputableBndrId name) => Pat name -> TcM a nPlusKPatInPatSynErr pat = failWithTc $ diff --git a/testsuite/tests/patsyn/should_run/T13688.hs b/testsuite/tests/patsyn/should_run/T13688.hs new file mode 100644 index 0000000..39b19fc --- /dev/null +++ b/testsuite/tests/patsyn/should_run/T13688.hs @@ -0,0 +1,21 @@ +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE QuasiQuotes #-} + +import T13688Quasi + +pattern A = [aQuoter|hello world|] + +pattern B <- [aQuoter|hello world|] + where B = [aQuoter|hello world|] + +main :: IO () +main = do + print A + case "hello world" of + A -> putStrLn "good" + _ -> putStrLn "bad" + + print B + case "hello world" of + B -> putStrLn "good" + _ -> putStrLn "bad" diff --git a/testsuite/tests/patsyn/should_run/T13688.stdout b/testsuite/tests/patsyn/should_run/T13688.stdout new file mode 100644 index 0000000..07bd598 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/T13688.stdout @@ -0,0 +1,4 @@ +"hello world" +good +"hello world" +good diff --git a/testsuite/tests/patsyn/should_run/T13688Quasi.hs b/testsuite/tests/patsyn/should_run/T13688Quasi.hs new file mode 100644 index 0000000..4302794 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/T13688Quasi.hs @@ -0,0 +1,12 @@ +module T13688Quasi where + +import Language.Haskell.TH.Quote +import Language.Haskell.TH.Syntax + +aQuoter :: QuasiQuoter +aQuoter = + QuasiQuoter { quotePat = return . LitP . StringL + , quoteExp = return . LitE . StringL + , quoteType = undefined + , quoteDec = undefined + } diff --git a/testsuite/tests/patsyn/should_run/all.T b/testsuite/tests/patsyn/should_run/all.T index d98a1ff..1498c1f 100644 --- a/testsuite/tests/patsyn/should_run/all.T +++ b/testsuite/tests/patsyn/should_run/all.T @@ -14,3 +14,4 @@ test('records-run', normal, compile_and_run, ['']) test('ghci', just_ghci, ghci_script, ['ghci.script']) test('T11985', just_ghci, ghci_script, ['T11985.script']) test('T11224', normal, compile_and_run, ['']) +test('T13688', normal, multimod_compile_and_run, ['T13688', '-v0']) From git at git.haskell.org Thu May 11 21:33:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 21:33:55 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Document requirement of at least one -dep-suffix (b9d1dae) Message-ID: <20170511213355.E8E073A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b9d1dae0c0ee0bd3b7e9be3c83ce932d837944f1/ghc >--------------------------------------------------------------- commit b9d1dae0c0ee0bd3b7e9be3c83ce932d837944f1 Author: Ben Gamari Date: Thu May 11 16:49:54 2017 -0400 users-guide: Document requirement of at least one -dep-suffix This requirement was introduced around 7.8 but was never documented. Resolves #9287. >--------------------------------------------------------------- b9d1dae0c0ee0bd3b7e9be3c83ce932d837944f1 docs/users_guide/separate_compilation.rst | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/docs/users_guide/separate_compilation.rst b/docs/users_guide/separate_compilation.rst index a140d46..0c981d5 100644 --- a/docs/users_guide/separate_compilation.rst +++ b/docs/users_guide/separate_compilation.rst @@ -1188,13 +1188,14 @@ generation are: .. ghc-flag:: -dep-suffix - Make extra dependencies that declare that files with suffix - ``._`` depend on interface files with suffix - ``._hi``, or (for ``{-# SOURCE #-}`` imports) on ``.hi-boot``. + Make dependencies that declare that files with suffix + ``.`` depend on interface files with suffix + ``.hi``, or (for ``{-# SOURCE #-}`` imports) on ``.hi-boot``. Multiple ``-dep-suffix`` flags are permitted. For example, - ``-dep-suffix a -dep-suffix b`` will make dependencies for ``.hs`` + ``-dep-suffix a_ -dep-suffix b_`` will make dependencies for ``.hs`` on ``.hi``, ``.a_hs`` on ``.a_hi``, and ``.b_hs`` on ``.b_hi``. - (Useful in conjunction with NoFib "ways".) + Note that you must provide at least one suffix; if you do not want a suffix + then pass ``-dep-suffix ''``. .. ghc-flag:: --exclude-module= From git at git.haskell.org Thu May 11 21:33:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 21:33:58 +0000 (UTC) Subject: [commit: ghc] master: Update autoconf scripts (06d2a50) Message-ID: <20170511213358.A9D313A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/06d2a50b447c3f6cc4f21e712e9c043618eb5941/ghc >--------------------------------------------------------------- commit 06d2a50b447c3f6cc4f21e712e9c043618eb5941 Author: Ben Gamari Date: Thu May 11 17:25:40 2017 -0400 Update autoconf scripts >--------------------------------------------------------------- 06d2a50b447c3f6cc4f21e712e9c043618eb5941 config.guess | 131 ++++++++++++++++--------------------- config.sub | 45 ++++--------- libraries/base/config.guess | 131 ++++++++++++++++--------------------- libraries/base/config.sub | 45 ++++--------- libraries/integer-gmp/config.guess | 131 ++++++++++++++++--------------------- libraries/integer-gmp/config.sub | 45 ++++--------- 6 files changed, 207 insertions(+), 321 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 06d2a50b447c3f6cc4f21e712e9c043618eb5941 From git at git.haskell.org Thu May 11 21:34:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 21:34:02 +0000 (UTC) Subject: [commit: ghc] master: Fix up tests for #13594 (3e79fe4) Message-ID: <20170511213402.252123A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3e79fe42b907653d97cd3a5496a8f133320354eb/ghc >--------------------------------------------------------------- commit 3e79fe42b907653d97cd3a5496a8f133320354eb Author: Ben Gamari Date: Thu May 11 17:30:31 2017 -0400 Fix up tests for #13594 This adds the GHCi variant of the failing program in #13594. Also, I inadvertently changed the T13594 test previously introduced in a way that made it no longer faithfully test the ticket as written. Fix this. >--------------------------------------------------------------- 3e79fe42b907653d97cd3a5496a8f133320354eb testsuite/tests/parser/should_compile/all.T | 1 - testsuite/tests/{parser => typecheck}/should_compile/T13594.hs | 2 +- testsuite/tests/typecheck/should_run/T13594a.script | 2 ++ testsuite/tests/typecheck/should_run/all.T | 2 ++ 4 files changed, 5 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/parser/should_compile/all.T b/testsuite/tests/parser/should_compile/all.T index 5cf615e..2059979 100644 --- a/testsuite/tests/parser/should_compile/all.T +++ b/testsuite/tests/parser/should_compile/all.T @@ -107,4 +107,3 @@ test('T10582', expect_broken(10582), compile, ['']) test('DumpParsedAst', normal, compile, ['-dsuppress-uniques -ddump-parsed-ast']) test('DumpRenamedAst', normal, compile, ['-dsuppress-uniques -ddump-rn-ast']) test('DumpTypecheckedAst', normal, compile, ['-dsuppress-uniques -ddump-tc-ast']) -test('T13594', normal, compile, ['']) diff --git a/testsuite/tests/parser/should_compile/T13594.hs b/testsuite/tests/typecheck/should_compile/T13594.hs similarity index 79% rename from testsuite/tests/parser/should_compile/T13594.hs rename to testsuite/tests/typecheck/should_compile/T13594.hs index 386d9c7..998d473 100644 --- a/testsuite/tests/parser/should_compile/T13594.hs +++ b/testsuite/tests/typecheck/should_compile/T13594.hs @@ -1,7 +1,7 @@ {-# LANGUAGE BangPatterns #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE RankNTypes #-} -{-# LANGUAGE NoMonomorphismRestriction #-} + module Bug where x :: forall a b. (a ~ Integer, b ~ Integer) => (a, b) diff --git a/testsuite/tests/typecheck/should_run/T13594a.script b/testsuite/tests/typecheck/should_run/T13594a.script new file mode 100644 index 0000000..dd1b92a --- /dev/null +++ b/testsuite/tests/typecheck/should_run/T13594a.script @@ -0,0 +1,2 @@ +:set -XBangPatterns -XRankNTypes -XTypeFamilies +let x :: forall a . a ~ Integer => forall b. b ~ Integer => (a, b); !x = (1, 2) diff --git a/testsuite/tests/typecheck/should_run/all.T b/testsuite/tests/typecheck/should_run/all.T index 0690f67..c8e921f 100755 --- a/testsuite/tests/typecheck/should_run/all.T +++ b/testsuite/tests/typecheck/should_run/all.T @@ -122,3 +122,5 @@ test('Typeable1', normal, compile_fail, ['']) test('TypeableEq', normal, compile_and_run, ['']) test('T13435', normal, compile_and_run, ['']) test('T11715', exit_code(1), compile_and_run, ['']) +test('T13594', expect_broken(13594), compile, ['']) +test('T13594a', expect_broken(13594), ghci_script, ['T13594a.script']) From git at git.haskell.org Thu May 11 22:24:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 22:24:43 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Fix location of T13594 test (3760303) Message-ID: <20170511222443.D0B9D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/37603032b1b159f325f7430f732abe00c79f1e24/ghc >--------------------------------------------------------------- commit 37603032b1b159f325f7430f732abe00c79f1e24 Author: Ben Gamari Date: Thu May 11 18:20:33 2017 -0400 testsuite: Fix location of T13594 test >--------------------------------------------------------------- 37603032b1b159f325f7430f732abe00c79f1e24 testsuite/tests/typecheck/should_compile/all.T | 1 + testsuite/tests/typecheck/should_run/all.T | 1 - 2 files changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 2f34144..4bfaf90 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -556,6 +556,7 @@ test('T13474', normal, compile, ['']) test('T13524', normal, compile, ['']) test('T13509', normal, compile, ['']) test('T13526', normal, compile, ['']) +test('T13594', expect_broken(13594), compile, ['']) test('T13603', normal, compile, ['']) test('T13333', normal, compile, ['']) test('T13585', [extra_files(['T13585.hs', 'T13585a.hs', 'T13585b.hs'])], run_command, ['$MAKE -s --no-print-directory T13585']) diff --git a/testsuite/tests/typecheck/should_run/all.T b/testsuite/tests/typecheck/should_run/all.T index c8e921f..ab5ab42 100755 --- a/testsuite/tests/typecheck/should_run/all.T +++ b/testsuite/tests/typecheck/should_run/all.T @@ -122,5 +122,4 @@ test('Typeable1', normal, compile_fail, ['']) test('TypeableEq', normal, compile_and_run, ['']) test('T13435', normal, compile_and_run, ['']) test('T11715', exit_code(1), compile_and_run, ['']) -test('T13594', expect_broken(13594), compile, ['']) test('T13594a', expect_broken(13594), ghci_script, ['T13594a.script']) From git at git.haskell.org Thu May 11 22:40:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 May 2017 22:40:32 +0000 (UTC) Subject: [commit: ghc] master: RnEnv refactoring (a3873e8) Message-ID: <20170511224032.EABAD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a3873e8cdec8fc966e91ebe024808376a4077e2b/ghc >--------------------------------------------------------------- commit a3873e8cdec8fc966e91ebe024808376a4077e2b Author: Matthew Pickering Date: Thu May 11 22:21:43 2017 +0100 RnEnv refactoring Summary: Lots of refactoring in RnEnv to reduce code duplication. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13545 Differential Revision: https://phabricator.haskell.org/D3507 >--------------------------------------------------------------- a3873e8cdec8fc966e91ebe024808376a4077e2b compiler/basicTypes/RdrName.hs | 7 +- compiler/parser/RdrHsSyn.hs | 4 +- compiler/rename/RnEnv.hs | 459 +++++++++++++-------- compiler/rename/RnExpr.hs | 12 +- compiler/rename/RnPat.hs | 6 +- compiler/rename/RnUtils.hs | 2 +- compiler/typecheck/TcRnExports.hs | 219 ++-------- compiler/typecheck/TcRnMonad.hs | 6 +- testsuite/tests/rename/should_compile/LookupSub.hs | 11 + .../tests/rename/should_compile/LookupSubA.hs | 4 + .../tests/rename/should_compile/LookupSubB.hs | 3 + testsuite/tests/rename/should_compile/all.T | 1 + 12 files changed, 357 insertions(+), 377 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 a3873e8cdec8fc966e91ebe024808376a4077e2b From git at git.haskell.org Fri May 12 01:45:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 May 2017 01:45:36 +0000 (UTC) Subject: [commit: ghc] master: Update autoconf scripts from correct source (410906b) Message-ID: <20170512014536.424C73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/410906b241f1ee5b338957acfc367f54e6d34fb1/ghc >--------------------------------------------------------------- commit 410906b241f1ee5b338957acfc367f54e6d34fb1 Author: Ben Gamari Date: Thu May 11 21:33:58 2017 -0400 Update autoconf scripts from correct source >--------------------------------------------------------------- 410906b241f1ee5b338957acfc367f54e6d34fb1 config.guess | 135 ++++++++++++++++++++----------------- config.sub | 45 ++++++++++--- libraries/base/config.guess | 135 ++++++++++++++++++++----------------- libraries/base/config.sub | 45 ++++++++++--- libraries/integer-gmp/config.guess | 135 ++++++++++++++++++++----------------- libraries/integer-gmp/config.sub | 45 ++++++++++--- 6 files changed, 327 insertions(+), 213 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 410906b241f1ee5b338957acfc367f54e6d34fb1 From git at git.haskell.org Fri May 12 08:07:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 May 2017 08:07:20 +0000 (UTC) Subject: [commit: ghc] master: Typos [ci skip] (09938f2) Message-ID: <20170512080720.CE40E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/09938f29cd615a3073f49f8b628650693e2f29e9/ghc >--------------------------------------------------------------- commit 09938f29cd615a3073f49f8b628650693e2f29e9 Author: Gabor Greif Date: Thu May 11 15:13:02 2017 +0200 Typos [ci skip] >--------------------------------------------------------------- 09938f29cd615a3073f49f8b628650693e2f29e9 aclocal.m4 | 2 +- compiler/basicTypes/DataCon.hs | 2 +- compiler/parser/Lexer.x | 8 ++++---- compiler/types/FamInstEnv.hs | 2 +- docs/users_guide/glasgow_exts.rst | 2 +- iserv/src/Remote/Slave.hs | 2 +- 6 files changed, 9 insertions(+), 9 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index a7920a7..697cba5 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -1879,7 +1879,7 @@ AC_DEFUN([GHC_CONVERT_VENDOR],[ # converts os from gnu to ghc naming, and assigns the result to $target_var AC_DEFUN([GHC_CONVERT_OS],[ case "$1" in - # watchos and tvos are ios variant as of May 2017. + # watchos and tvos are ios variants as of May 2017. ios|watchos|tvos) $3="ios" ;; diff --git a/compiler/basicTypes/DataCon.hs b/compiler/basicTypes/DataCon.hs index acd2865..60cffac 100644 --- a/compiler/basicTypes/DataCon.hs +++ b/compiler/basicTypes/DataCon.hs @@ -233,7 +233,7 @@ It's a flaw in the language. it separately in the type checker on occurrences of a constructor, either in an expression or in a pattern. - [May 2003: actually I think this decision could evasily be + [May 2003: actually I think this decision could easily be reversed now, and probably should be. Generics could be disabled for types with a stupid context; record updates now (H98) needs the context too; etc. It's an unforced change, so diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x index 6ebd087..2ce0ac6 100644 --- a/compiler/parser/Lexer.x +++ b/compiler/parser/Lexer.x @@ -2524,7 +2524,7 @@ alternativeLayoutRuleToken t (_, ALRLayout _ col : _ls, Just expectingOCurly) | (thisCol > col) || (thisCol == col && - isNonDecreasingIntentation expectingOCurly) -> + isNonDecreasingIndentation expectingOCurly) -> do setAlrExpectingOCurly Nothing setALRContext (ALRLayout expectingOCurly thisCol : context) setNextToken t @@ -2668,9 +2668,9 @@ isALRclose ITccurly = True isALRclose ITcubxparen = True isALRclose _ = False -isNonDecreasingIntentation :: ALRLayout -> Bool -isNonDecreasingIntentation ALRLayoutDo = True -isNonDecreasingIntentation _ = False +isNonDecreasingIndentation :: ALRLayout -> Bool +isNonDecreasingIndentation ALRLayoutDo = True +isNonDecreasingIndentation _ = False containsCommas :: Token -> Bool containsCommas IToparen = True diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs index 89f4214..6d179a9 100644 --- a/compiler/types/FamInstEnv.hs +++ b/compiler/types/FamInstEnv.hs @@ -849,7 +849,7 @@ lookupFamInstEnvInjectivityConflicts -- INVARIANT: list contains at least one True value -> FamInstEnvs -- all type instances seens so far -> FamInst -- new type instance that we're checking - -> [CoAxBranch] -- conflicting instance delcarations + -> [CoAxBranch] -- conflicting instance declarations lookupFamInstEnvInjectivityConflicts injList (pkg_ie, home_ie) fam_inst@(FamInst { fi_axiom = new_axiom }) -- See Note [Verifying injectivity annotation]. This function implements diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 2b7b652..729cd4d 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -9497,7 +9497,7 @@ Here are the details: visible type application. * Universal variables always come first, in precisely the order they - appear in the type delcaration. Universal variables that are + appear in the type declaration. Universal variables that are constrained by a GADT return type are not included in the data constructor. * Existential variables come next. Their order is determined by a user- diff --git a/iserv/src/Remote/Slave.hs b/iserv/src/Remote/Slave.hs index c7210dc..11cc68a 100644 --- a/iserv/src/Remote/Slave.hs +++ b/iserv/src/Remote/Slave.hs @@ -30,7 +30,7 @@ dropLeadingPathSeparator :: FilePath -> FilePath dropLeadingPathSeparator p | isAbsolute p = joinPath (drop 1 (splitPath p)) | otherwise = p --- | Path concatication that prevents a double path separator to appear in the +-- | Path concatenation that prevents a double path separator to appear in the -- final path. "/foo/bar/" "/baz/quux" == "/foo/bar/baz/quux" () :: FilePath -> FilePath -> FilePath lhs rhs = dropTrailingPathSeparator lhs dropLeadingPathSeparator rhs From git at git.haskell.org Fri May 12 13:08:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 May 2017 13:08:14 +0000 (UTC) Subject: [commit: ghc] master: Add regression tests for #12083 (01af8ae) Message-ID: <20170512130814.36D483A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/01af8aee30c743ab505e164ac9aa02149fbe4b9e/ghc >--------------------------------------------------------------- commit 01af8aee30c743ab505e164ac9aa02149fbe4b9e Author: Ryan Scott Date: Fri May 12 08:54:30 2017 -0400 Add regression tests for #12083 Summary: Commit 0c9d9dec0a924a4f34f4cff26d004143c028861a (the fix for #13271) fixed the programs in #12083. This adds regression tests for them. Test Plan: make test TEST="T12083a T12083b" Reviewers: austin, bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #12083 Differential Revision: https://phabricator.haskell.org/D3573 >--------------------------------------------------------------- 01af8aee30c743ab505e164ac9aa02149fbe4b9e testsuite/tests/typecheck/should_fail/T12083a.hs | 19 +++++++++++++++++++ testsuite/tests/typecheck/should_fail/T12083a.stderr | 12 ++++++++++++ testsuite/tests/typecheck/should_fail/T12083b.hs | 9 +++++++++ testsuite/tests/typecheck/should_fail/T12083b.stderr | 7 +++++++ testsuite/tests/typecheck/should_fail/all.T | 2 ++ 5 files changed, 49 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T12083a.hs b/testsuite/tests/typecheck/should_fail/T12083a.hs new file mode 100644 index 0000000..0ca86f7 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T12083a.hs @@ -0,0 +1,19 @@ +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE UnicodeSyntax #-} +module T12803a where + +type Constrd a = Num a ⇒ a + +data ADT a = ADT (Constrd a) ExistentiallyLost + +data ExistentiallyLost = ∀ u. TC u ⇒ ExistentiallyLost u + +class u ~ (ATF1 u, ATF2 u) ⇒ TC u where + type ATF1 u ∷ * + type ATF2 u ∷ * + uie_handlers ∷ ADT Int + +-- Loop: +-- - ADT depends on ExistentiallyLost (also the Constrd appendage) +-- - ExistentiallyLost depends on TC +-- - TC depends on ADT diff --git a/testsuite/tests/typecheck/should_fail/T12083a.stderr b/testsuite/tests/typecheck/should_fail/T12083a.stderr new file mode 100644 index 0000000..dc1452d --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T12083a.stderr @@ -0,0 +1,12 @@ + +T12083a.hs:5:1: error: + • Illegal qualified type: Num a => a + Perhaps you intended to use RankNTypes or Rank2Types + • In the type synonym declaration for ‘Constrd’ + +T12083a.hs:9:26: error: + • Data constructor ‘ExistentiallyLost’ has existential type variables, a context, or a specialised result type + ExistentiallyLost :: forall u. TC u => u -> ExistentiallyLost + (Use ExistentialQuantification or GADTs to allow this) + • In the definition of data constructor ‘ExistentiallyLost’ + In the data type declaration for ‘ExistentiallyLost’ diff --git a/testsuite/tests/typecheck/should_fail/T12083b.hs b/testsuite/tests/typecheck/should_fail/T12083b.hs new file mode 100644 index 0000000..3992db3 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T12083b.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE GADTs #-} + +module T12083b where + +class Class a where + test :: a -> (Eq a => r) -> r + +data P a b where + Con :: (Class a, a ~ b) => P a b diff --git a/testsuite/tests/typecheck/should_fail/T12083b.stderr b/testsuite/tests/typecheck/should_fail/T12083b.stderr new file mode 100644 index 0000000..39ceece --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T12083b.stderr @@ -0,0 +1,7 @@ + +T12083b.hs:6:5: error: + • Illegal qualified type: Eq a => r + Perhaps you intended to use RankNTypes or Rank2Types + • When checking the class method: + test :: forall a. Class a => forall r. a -> (Eq a => r) -> r + In the class declaration for ‘Class’ diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 3875063..cf2c3c8 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -404,6 +404,8 @@ test('T12035', [], multimod_compile_fail, ['T12035', '-v0']) test('T12035j', [extra_files(['T12035.hs', 'T12035a.hs', 'T12035.hs-boot']), req_smp], multimod_compile_fail, ['T12035', '-j2 -v0']) test('T12063', [expect_broken(12063)], multimod_compile_fail, ['T12063', '-v0']) +test('T12083a', normal, compile_fail, ['']) +test('T12083b', normal, compile_fail, ['']) test('T11974b', normal, compile_fail, ['']) test('T12151', normal, compile_fail, ['']) test('T7437', normal, compile_fail, ['']) From git at git.haskell.org Fri May 12 13:08:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 May 2017 13:08:17 +0000 (UTC) Subject: [commit: ghc] master: Add regression test for #11966 (ba5114e) Message-ID: <20170512130817.5C39C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ba5114e310e9140f2b4987245ba1f3709c7b06ec/ghc >--------------------------------------------------------------- commit ba5114e310e9140f2b4987245ba1f3709c7b06ec Author: Ryan Scott Date: Fri May 12 08:57:26 2017 -0400 Add regression test for #11966 Commit a7ee2d4c4229b27af324ebac93081f692835365d fixed #11966. Here's a regression test for it. >--------------------------------------------------------------- ba5114e310e9140f2b4987245ba1f3709c7b06ec testsuite/tests/dependent/should_compile/T11966.hs | 34 ++++++++++++++++++++++ testsuite/tests/dependent/should_compile/all.T | 1 + 2 files changed, 35 insertions(+) diff --git a/testsuite/tests/dependent/should_compile/T11966.hs b/testsuite/tests/dependent/should_compile/T11966.hs new file mode 100644 index 0000000..0262a0a --- /dev/null +++ b/testsuite/tests/dependent/should_compile/T11966.hs @@ -0,0 +1,34 @@ +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE KindSignatures #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE TypeInType #-} +{-# LANGUAGE TypeOperators #-} + +module T11966 where + +import Data.Kind (Type) +import GHC.TypeLits (Symbol) + +-- Simplification +type family Col (f :: k -> j) (x :: k) :: Type + +-- Base types +data PGBaseType = PGInteger | PGText + +-- Transformations +data Column t = Column Symbol t +newtype Nullable t = Nullable t +newtype HasDefault t = HasDefault t + +-- Interpretations +data Expr k + +data Record (f :: forall k. k -> Type) = + Record {rX :: Col f ('Column "x" 'PGInteger) + ,rY :: Col f ('Column "y" ('Nullable 'PGInteger)) + ,rZ :: Col f ('HasDefault 'PGText)} + +x :: Record Expr +x = undefined diff --git a/testsuite/tests/dependent/should_compile/all.T b/testsuite/tests/dependent/should_compile/all.T index a921743..8a9b221 100644 --- a/testsuite/tests/dependent/should_compile/all.T +++ b/testsuite/tests/dependent/should_compile/all.T @@ -21,5 +21,6 @@ test('T11711', normal, compile, ['']) test('RaeJobTalk', normal, compile, ['']) test('T11635', normal, compile, ['']) test('T11719', normal, compile, ['']) +test('T11966', normal, compile, ['']) test('T12442', normal, compile, ['']) test('T13538', normal, compile, ['']) From git at git.haskell.org Fri May 12 13:08:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 May 2017 13:08:20 +0000 (UTC) Subject: [commit: ghc] master: Add regression test for #11964 (a13adcf) Message-ID: <20170512130820.8B4EC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a13adcf8cfc650979a80101c0879c11a507734f9/ghc >--------------------------------------------------------------- commit a13adcf8cfc650979a80101c0879c11a507734f9 Author: Ryan Scott Date: Fri May 12 09:06:24 2017 -0400 Add regression test for #11964 This issue was only ever present in the GHC 8.0.1 release candidates, but let's add a regression test for it just to be safe. >--------------------------------------------------------------- a13adcf8cfc650979a80101c0879c11a507734f9 testsuite/tests/dependent/should_run/T11964.hs | 10 ++++++++++ testsuite/tests/dependent/should_run/T11964a.hs | 5 +++++ testsuite/tests/dependent/should_run/all.T | 2 +- 3 files changed, 16 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/dependent/should_run/T11964.hs b/testsuite/tests/dependent/should_run/T11964.hs new file mode 100644 index 0000000..96a83dc --- /dev/null +++ b/testsuite/tests/dependent/should_run/T11964.hs @@ -0,0 +1,10 @@ +module T11964 where + +import Data.Kind +import T11964a + +t1 :: T Type Int +t1 = T () + +t2 :: T Star Int +t2 = T () diff --git a/testsuite/tests/dependent/should_run/T11964a.hs b/testsuite/tests/dependent/should_run/T11964a.hs new file mode 100644 index 0000000..f057654 --- /dev/null +++ b/testsuite/tests/dependent/should_run/T11964a.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE TypeInType #-} +module T11964a where +import Data.Kind +type Star = Type +newtype T k (t :: k) = T () diff --git a/testsuite/tests/dependent/should_run/all.T b/testsuite/tests/dependent/should_run/all.T index c3b18c1..29877a7 100755 --- a/testsuite/tests/dependent/should_run/all.T +++ b/testsuite/tests/dependent/should_run/all.T @@ -1,4 +1,4 @@ # test('T11311', normal, compile_and_run, ['']) - +test('T11964', normal, multimod_compile, ['T11964', '-v0']) From git at git.haskell.org Fri May 12 18:38:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 May 2017 18:38:44 +0000 (UTC) Subject: [commit: ghc] master: Automatically add SCCs to INLINABLE bindings (ab91daf) Message-ID: <20170512183844.DD85E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ab91daf2cb8a4a8558727ebe30a662a2ddf290e1/ghc >--------------------------------------------------------------- commit ab91daf2cb8a4a8558727ebe30a662a2ddf290e1 Author: David Feuer Date: Fri May 12 14:37:36 2017 -0400 Automatically add SCCs to INLINABLE bindings Instead of excluding `isAnyInlinePragma`, just exclude `isInlinePragma`. This makes GHC behave as documented; the user's guide only indicates that GHC does not automatically add SCCs to `INLINE` bindings. Fixes #12962. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: DemiMarie, osa1, Mikolaj, simonpj, rwbarton, thomie GHC Trac Issues: #12962 Differential Revision: https://phabricator.haskell.org/D3550 >--------------------------------------------------------------- ab91daf2cb8a4a8558727ebe30a662a2ddf290e1 compiler/deSugar/Coverage.hs | 14 ++++++-- testsuite/tests/profiling/should_run/T12962.hs | 21 ++++++++++++ .../tests/profiling/should_run/T12962.prof.sample | 32 ++++++++++++++++++ testsuite/tests/profiling/should_run/all.T | 2 ++ .../profiling/should_run/profinline001.prof.sample | 39 ++++++++++++---------- 5 files changed, 87 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 ab91daf2cb8a4a8558727ebe30a662a2ddf290e1 From git at git.haskell.org Fri May 12 22:31:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 May 2017 22:31:15 +0000 (UTC) Subject: [commit: ghc] master: Revert "Treat banged bindings as FunBinds" (3032ae8) Message-ID: <20170512223115.0263B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3032ae81dd14c2eaefa9ecd8880dafa9bda104d9/ghc >--------------------------------------------------------------- commit 3032ae81dd14c2eaefa9ecd8880dafa9bda104d9 Author: Ben Gamari Date: Fri May 12 16:59:33 2017 -0400 Revert "Treat banged bindings as FunBinds" This partially reverts commit 372995364c52eef15066132d7d1ea8b6760034e6 as it doesn't actually fix #13594. Namely it does not revert the mkPrefixFunRhs refactoring since this is rather independent from the functional changes. Going to try again with a whole working patch >--------------------------------------------------------------- 3032ae81dd14c2eaefa9ecd8880dafa9bda104d9 compiler/deSugar/Check.hs | 6 ++-- compiler/hsSyn/HsBinds.hs | 40 ++-------------------- compiler/hsSyn/HsExpr.hs | 26 +++++--------- compiler/hsSyn/HsUtils.hs | 4 +-- compiler/parser/Parser.y | 34 +++++++----------- compiler/parser/RdrHsSyn.hs | 16 ++++----- compiler/rename/RnBinds.hs | 4 +-- .../parser/should_compile/DumpParsedAst.stderr | 3 +- .../parser/should_compile/DumpRenamedAst.stderr | 3 +- .../should_compile/DumpTypecheckedAst.stderr | 3 +- 10 files changed, 40 insertions(+), 99 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 3032ae81dd14c2eaefa9ecd8880dafa9bda104d9 From git at git.haskell.org Fri May 12 22:31:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 May 2017 22:31:17 +0000 (UTC) Subject: [commit: ghc] master: Fix crash in isModuleInterpreted for HsBoot (fixes #13591) (1edee7a) Message-ID: <20170512223117.B30023A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1edee7a8b5ca24156cb6e21bde6d611a0ba63882/ghc >--------------------------------------------------------------- commit 1edee7a8b5ca24156cb6e21bde6d611a0ba63882 Author: Lennart Spitzner Date: Wed May 10 16:47:19 2017 +0200 Fix crash in isModuleInterpreted for HsBoot (fixes #13591) Rename isModuleInterpreted to moduleIsBootOrNotObjectLinkable because a) there already is a moduleIsInterpreted function in the same module b) I have no idea if the (new) semantic of the bool returned matches some understanding of "is interpreted". >--------------------------------------------------------------- 1edee7a8b5ca24156cb6e21bde6d611a0ba63882 compiler/main/GHC.hs | 2 +- compiler/main/InteractiveEval.hs | 14 +++++++------- ghc/GHCi/UI.hs | 2 +- 3 files changed, 9 insertions(+), 9 deletions(-) diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index 53e135c..0f7acbf 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -112,7 +112,7 @@ module GHC ( moduleIsInterpreted, getInfo, showModule, - isModuleInterpreted, + moduleIsBootOrNotObjectLinkable, -- ** Inspecting types and kinds exprType, TcRnExprMode(..), diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs index 1fa2698..0d83b48 100644 --- a/compiler/main/InteractiveEval.hs +++ b/compiler/main/InteractiveEval.hs @@ -31,7 +31,7 @@ module InteractiveEval ( typeKind, parseName, showModule, - isModuleInterpreted, + moduleIsBootOrNotObjectLinkable, parseExpr, compileParsedExpr, compileExpr, dynCompileExpr, compileExprRemote, compileParsedExprRemote, @@ -901,17 +901,17 @@ dynCompileExpr expr = do showModule :: GhcMonad m => ModSummary -> m String showModule mod_summary = withSession $ \hsc_env -> do - interpreted <- isModuleInterpreted mod_summary + interpreted <- moduleIsBootOrNotObjectLinkable mod_summary let dflags = hsc_dflags hsc_env return (showModMsg dflags (hscTarget dflags) interpreted mod_summary) -isModuleInterpreted :: GhcMonad m => ModSummary -> m Bool -isModuleInterpreted mod_summary = withSession $ \hsc_env -> +moduleIsBootOrNotObjectLinkable :: GhcMonad m => ModSummary -> m Bool +moduleIsBootOrNotObjectLinkable mod_summary = withSession $ \hsc_env -> case lookupHpt (hsc_HPT hsc_env) (ms_mod_name mod_summary) of Nothing -> panic "missing linkable" - Just mod_info -> return (not obj_linkable) - where - obj_linkable = isObjectLinkable (expectJust "showModule" (hm_linkable mod_info)) + Just mod_info -> return $ case hm_linkable mod_info of + Nothing -> True + Just linkable -> not (isObjectLinkable linkable) ---------------------------------------------------------------------------- -- RTTI primitives diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs index 52a809e..6954002 100644 --- a/ghc/GHCi/UI.hs +++ b/ghc/GHCi/UI.hs @@ -1801,7 +1801,7 @@ modulesLoadedMsg ok mods = do dflags <- getDynFlags unqual <- GHC.getPrintUnqual let mod_name mod = do - is_interpreted <- GHC.isModuleInterpreted mod + is_interpreted <- GHC.moduleIsBootOrNotObjectLinkable mod return $ if is_interpreted then ppr (GHC.ms_mod mod) else ppr (GHC.ms_mod mod) From git at git.haskell.org Fri May 12 22:31:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 May 2017 22:31:20 +0000 (UTC) Subject: [commit: ghc] master: Bump haddock submodule (8fd7442) Message-ID: <20170512223120.69B0F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8fd7442efcf6ef0a274f51657633818bd878eb5c/ghc >--------------------------------------------------------------- commit 8fd7442efcf6ef0a274f51657633818bd878eb5c Author: Ben Gamari Date: Fri May 12 14:48:03 2017 -0400 Bump haddock submodule Fixes lazy IO bug >--------------------------------------------------------------- 8fd7442efcf6ef0a274f51657633818bd878eb5c utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index a0c4790..b7d7b7a 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit a0c4790e15a2d3fab8d830eee8fcd639fe6d39c9 +Subproject commit b7d7b7acd42cbe424afde3c8a5a59a0706445343 From git at git.haskell.org Fri May 12 22:31:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 May 2017 22:31:23 +0000 (UTC) Subject: [commit: ghc] master: Render \t as 8 spaces in caret diagnostics (c068c38) Message-ID: <20170512223123.28CEA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c068c38727b7bd7a1a75495167f7470abb7bf866/ghc >--------------------------------------------------------------- commit c068c38727b7bd7a1a75495167f7470abb7bf866 Author: Phil Ruffwind Date: Thu May 11 15:41:08 2017 -0400 Render \t as 8 spaces in caret diagnostics Test Plan: validate Reviewers: austin, bgamari, rwbarton Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13664 Differential Revision: https://phabricator.haskell.org/D3549 >--------------------------------------------------------------- c068c38727b7bd7a1a75495167f7470abb7bf866 compiler/main/ErrUtils.hs | 10 +++++++--- testsuite/driver/testlib.py | 14 ++++++++++++-- testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs | 3 +++ .../tests/warnings/should_fail/CaretDiagnostics1.stderr | 8 ++++++++ testsuite/tests/warnings/should_fail/all.T | 15 ++++++++++++++- 5 files changed, 44 insertions(+), 6 deletions(-) diff --git a/compiler/main/ErrUtils.hs b/compiler/main/ErrUtils.hs index ded7085..d87d2b2 100644 --- a/compiler/main/ErrUtils.hs +++ b/compiler/main/ErrUtils.hs @@ -261,8 +261,6 @@ getCaretDiagnostic severity (RealSrcSpan span) = do rowStr = show row multiline = row /= srcSpanEndLine span - stripNewlines = filter (/= '\n') - caretDiagnostic Nothing = empty caretDiagnostic (Just srcLineWithNewline) = sdocWithDynFlags $ \ dflags -> @@ -280,7 +278,13 @@ getCaretDiagnostic severity (RealSrcSpan span) = do where - srcLine = stripNewlines srcLineWithNewline + fixWhitespace (i, c) + | c == '\n' = "" + -- show tabs in a device-independent manner #13664 + | c == '\t' = replicate (8 - i `mod` 8) ' ' + | otherwise = [c] + + srcLine = concat (map fixWhitespace (zip [0..] srcLineWithNewline)) start = srcSpanStartCol span - 1 end | multiline = length srcLine diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 1f08f5b..b730685 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -84,6 +84,8 @@ def setTestOpts( f ): # test('test001', expect_fail, compile, ['']) # # to expect failure for this test. +# +# type TestOpt = (name :: String, opts :: Object) -> IO () def normal( name, opts ): return; @@ -518,6 +520,12 @@ def normalise_errmsg_fun( *fs ): def _normalise_errmsg_fun( name, opts, *fs ): opts.extra_errmsg_normaliser = join_normalisers(opts.extra_errmsg_normaliser, fs) +def normalise_whitespace_fun(f): + return lambda name, opts: _normalise_whitespace_fun(name, opts, f) + +def _normalise_whitespace_fun(name, opts, f): + opts.whitespace_normaliser = f + def normalise_version_( *pkgs ): def normalise_version__( str ): return re.sub('(' + '|'.join(map(re.escape,pkgs)) + ')-[0-9.]+', @@ -622,7 +630,7 @@ def runTest(watcher, opts, name, func, args): test_common_work(watcher, name, opts, func, args) # name :: String -# setup :: TestOpts -> IO () +# setup :: [TestOpt] -> IO () def test(name, setup, func, args): global aloneTests global parallelTests @@ -1006,7 +1014,9 @@ def do_compile(name, way, should_fail, top_mod, extra_mods, extra_hc_opts, **kwa join_normalisers(getTestOpts().extra_errmsg_normaliser, normalise_errmsg), expected_stderr_file, actual_stderr_file, - whitespace_normaliser=normalise_whitespace): + whitespace_normaliser=getattr(getTestOpts(), + "whitespace_normaliser", + normalise_whitespace)): return failBecause('stderr mismatch') # no problems found, this test passed diff --git a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs index 6ecadf6..3ebb5ee 100644 --- a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs +++ b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs @@ -15,3 +15,6 @@ main = do fóo :: Int fóo = () + +tabby :: Int +tabby = () diff --git a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr index 68fbfa7..600b7c7 100644 --- a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr +++ b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr @@ -70,3 +70,11 @@ CaretDiagnostics1.hs:17:7-8: error: | 17 | fóo = () | ^^ + +CaretDiagnostics1.hs:20:17-18: error: + • Couldn't match expected type ‘Int’ with actual type ‘()’ + • In the expression: () + In an equation for ‘tabby’: tabby = () + | +20 | tabby = () + | ^^ diff --git a/testsuite/tests/warnings/should_fail/all.T b/testsuite/tests/warnings/should_fail/all.T index 71a7a97..73117a9 100644 --- a/testsuite/tests/warnings/should_fail/all.T +++ b/testsuite/tests/warnings/should_fail/all.T @@ -1,3 +1,16 @@ +import re + +def normalise_whitespace_carefully(s): + # Merge contiguous whitespace characters into a single space + # except on caret diagnostic lines + return '\n'.join(line + if re.match(r'\s*\d*\s*\|', line) + else ' '.join(w for w in line.split()) + for line in s.split('\n')) + test('WerrorFail', normal, compile_fail, ['']) -test('CaretDiagnostics1', normal, compile_fail, ['-fdiagnostics-show-caret -ferror-spans']) +test('CaretDiagnostics1', + [normalise_whitespace_fun(normalise_whitespace_carefully)], + compile_fail, + ['-fdiagnostics-show-caret -ferror-spans']) test('CaretDiagnostics2', normal, compile_fail, ['-fdiagnostics-show-caret']) From git at git.haskell.org Sat May 13 03:28:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 13 May 2017 03:28:28 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Testing simpler Jenkinsfile (947b294) Message-ID: <20170513032828.4B5E13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/947b294bbde7cb950c5ff59f6a49c25ab17ccc73/ghc >--------------------------------------------------------------- commit 947b294bbde7cb950c5ff59f6a49c25ab17ccc73 Author: Ben Gamari Date: Fri Apr 21 14:29:34 2017 -0400 Testing simpler Jenkinsfile >--------------------------------------------------------------- 947b294bbde7cb950c5ff59f6a49c25ab17ccc73 Jenkinsfile | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) diff --git a/Jenkinsfile b/Jenkinsfile new file mode 100644 index 0000000..7ff08f0 --- /dev/null +++ b/Jenkinsfile @@ -0,0 +1,16 @@ +pipeline { + agent any + stages { + stage('Build') { + steps { + sh 'git submodule update --init --recursive' + sh ''' + ./boot + ./configure --enable-tarballs-autodownload + make -j$THREADS + make THREADS=$THREADS test + ''' + } + } + } +} From git at git.haskell.org Sat May 13 03:28:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 13 May 2017 03:28:31 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Testing (38cc04e) Message-ID: <20170513032831.0397D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/38cc04e12df7cc11b995e44a40ba4438131c3e81/ghc >--------------------------------------------------------------- commit 38cc04e12df7cc11b995e44a40ba4438131c3e81 Author: Ben Gamari Date: Fri Apr 28 09:53:13 2017 -0400 Testing >--------------------------------------------------------------- 38cc04e12df7cc11b995e44a40ba4438131c3e81 Jenkinsfile | 30 +++++++++++++++++------------- 1 file changed, 17 insertions(+), 13 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 7ff08f0..f643e51 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,16 +1,20 @@ pipeline { - agent any - stages { - stage('Build') { - steps { - sh 'git submodule update --init --recursive' - sh ''' - ./boot - ./configure --enable-tarballs-autodownload - make -j$THREADS - make THREADS=$THREADS test - ''' - } - } + agent any + parameters { + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') + } + + stages { + stage('Build') { + steps { + sh 'git submodule update --init --recursive' + sh ''' + ./boot + ./configure --enable-tarballs-autodownload + make -j$THREADS + make THREADS=$THREADS test + ''' + } } + } } From git at git.haskell.org Sat May 13 03:28:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 13 May 2017 03:28:34 +0000 (UTC) Subject: [commit: ghc] wip/jenkins's head updated: Testing (38cc04e) Message-ID: <20170513032834.5EA933A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/jenkins' now includes: 32a5ba9 Build system: fix bindist for cross-build GHC 58a59d0 Sync up terminfo submodule to 0.4.1.0 release tag 9dd20a3 Edit eventlog-formats.rst to match implementation 363f7fd testsuite: Update performance metrics 3d7c489 base: update comment to match the change from e134af01 c35d63b Bump deepseeq submodule bf67dc7 Bump filepath submodule 5eebb11 Bump time submodule 6cffee6 Haddock submodule update. 8e93799 skip T13525 when running on Windows. f446f6a First update mingw-w64 packages for 8.4 58a6569 configure.ac: print paths to dllwrap and windres fe37e2c aclocal.m4: treat '*-w64-mingw32' targets as windows 745032d rts: tweak cross-compilation to mingw32 0d975a6 Minor reordering of `#include`s fixing compilation on AIX 2fa6873 Fix compilation for !HAVE_FLOCK 8908ba3 ghc: tweak cross-compilation to mingw32 74e5ec9 ghc.mk: fix 'make install' for cross-mingw32 87fbf39 win32/Ticker: Stop ticker on exit f13eebc cpp: Use #pragma once instead of #ifndef guards 1d66f10 rts: Fix "ASSERT ("s e5e8646 [linker] Adds ElfTypes 9eea43f [linker] Adds elf_compat.h, util.h, elf_util.h 18c3a7e Document the kind generalization behavior observed in #13555 317ceb4 Only build iserv with -threaded if GhcThreaded is set f6eaf01 testsuite: Add test for #13591 907b0f3 testsuite: Add testcase for #13587 3efa5be testsuite: Increase T13056 window size to +/-10% 868bdcc testsuite: Add testcase for #13075 1f4fd37 Export function for use in GHC API f799df5 testsuite: Mark T13075 as broken due to #13075 ab27fdc Add regression test for #13603 d5cb4d2 Disable terminfo, if we don’t build it. b68697e compiler/cmm/PprC.hs: constify labels in .rodata 6f9f5ff testsuite/driver: Fix deletion retry logic on Windows 1c27e5b Add failing test case for T13611 cd10a23 Guard yet another /bin/sh `for in` loop against empty vars 583fa9e core-spec: Simplify the handling of LetRec 914842e Don't setProgramDynFlags on every :load 688272b Don't describe tuple sections as "Python-style" 6610886 Revert "Remove special casing of Windows in generic files" 9373994 configure: Kill off FP_ARG_WITH_* 89a3241 PPC NCG: Implement callish prim ops 71c3cea Add backup url and sync support for Win32 tarball script da792e4 Only pretty-print binders in closed type families with -fprint-explicit-foralls 2446026 Document mkWeak# 47be644 Add instances for Data.Ord.Down 350d268 Update hsc2hs submodule to 0.68.2 579bb76 Update Cabal submodule, with necessary wibbles. 2744c94 Bump process to 1.6 7f6674d Comments and tiny refactoring 6c2d917 A bit more tcTrace 4d5ab1f Comments only 03ec792 Comments only 25754c8 Eta expansion and join points a1b753e Cure exponential behaviour in the simplifier 29d88ee Be a bit more eager to inline in a strict context ba597c1 get-win32-tarballs: Grab perl tarball from haskell.org, not GitHub 69b9b85 Add regression test for #12104 b2c38d6 Make the tyvars in TH-reified data family instances uniform 228d467 Use memcpy in cloneArray 9f9b90f CSE: Fix cut and paste error 9ac2218 nativeGen: Use SSE2 SQRT instruction 1cae73a Move dataConTagZ to DataCon 193664d Re-engineer caseRules to add tagToEnum/dataToTag 6d14c14 Improve code generation for conditionals e5b3492 Enable new warning for fragile/incorrect CPP #if usage 945c45a Prefer #if defined to #ifdef 41d9a79 Remove unused tidyOccNames and update Note 821a9f9 testsuite: Widen acceptance window of T13379 0ff7bc8 Update broken nm message 46923b6 Disable -Wcpp-undef for now 7567b9d Ignore ANN pragmas with no TH and no external interpreter. 18fbb9d testsuite: Add test for #13609 c04bd55 Fix capitalization in message for #13609 667abf1 Make LLVM output robust to -dead_strip on mach-o platforms 068af01 PPC NCG: Lower MO_*_Fabs as PowerPC fabs instruction 5c602d2 Avoid excessive space usage from unfoldings in CoreTidy e250178 [linker] Add ocInit/ocDeinit for ELF f2c35d7 Bump array submodule 3746f62 testsuite: Bump allocations of T3064 c46a600 Improve SpecConstr when there are many opportunities 71037b6 Join-point refactoring ff23978 Fix a small Float-Out bug 9e47dc4 Fix loss-of-SpecConstr bug b1aede6 Typos in manual and comments b460d6c Fix #13233 by checking for lev-poly primops ef0ff34 Shave the hair off mkCastTy. 466803a Use mkCastTy in subst_ty. 09bf135 Fix #13333 by fixing the covar's type in ctEvCoercion 16b0a07 Fix #13233 by checking for lev-poly primops 6df8bef Test #13585 in typecheck/should_compile/T13585 239418c Improve fixIO 783dfa7 Teach optCoecion about FunCo 81af480 Abandon typedefing the {Section,ObjectCode}FormatInfo structs e770197 Deal with exceptions in dsWhenNoErrs 2a33f17 Remove unused import 2a09700 Comments only, about Typeable/TypeRep/KindRep cb850e0 Add test for #13320 8a60550 rts: Fix MachO from D3527 41a00fa Bump nofib submodule a660844 Add an Eq instance for UniqSet db10b79 Pass -ffrontend-opt arguments to frontend plugin in the correct order 0b41bbc user-guide: fix links to compact region 4fcaf8e Fix comment for compact region 03ca391 Add regression test for #11616 74f3153 Fix markdown for new GitHub Flavored Markdown 1829d26 Implement sequential name lookup properly 8a2c247 hpc: Output a legend at the top of output files b3da6a6 CoreTidy: Don't seq unfoldings c8e4d4b TcTypeable: Simplify 02748a5 Typos in comments [ci skip] a483e71 tweak to minimize diff against ocInit_ELF 38a3819 Add regression tests for #12947, #13640 4a6cb5e Add testsuite/timeout/TimeMe to .gitignore ed0c7f8 Add regression test for #13651 baa18de testsuite: add new test for desugar warnings/errors with -fno-code 1840121 base: Fix documentation for forkIOWithUnmask 579749d Bump Cabal submodule to the 2.0.0.0 tag c685a44 [Docs] Prefer cost centre 476307c users-guide: Fix a variety of warnings 87ff5d4 OptCoercion: Ensure that TyConApps match in arity ff7a3c4 Optimize casMutVar# for single-threaded RTS dc3b4af Fix Raspberry Pi 0279b74 Make XNegativeLiterals treat -0.0 as negative 0 c5b28e0 Add a failing test for T13644 b99bae6 Dataflow: use IntSet for mkDepBlocks 3729953 Treat banged bindings as FunBinds 85bfd0c testsuite: Fix attribution of "Don't seq unfoldings" regression d46a510 Use mkSymCo in OptCoercion.wrapSym 549c8b3 Don't warn about variable-free strict pattern bindings 6f26fe7 Add regression test for Trac #13659 cb5ca5f Make CallInfo into a data type with fields 43a3168 Reset cc_pend_sc flag in dropDerivedCt 8e72a2e Revert "CoreTidy: Don't seq unfoldings" 22a03e7 Typos [ci skip] 26f509a Efficient membership for home modules 1893ba1 Fix a performance bug in GhcMake.downsweep 4d9167b testsuite: Update allocations for T4801 on Darwin 63ba812 mailmap: Add Douglas Wilson 8d4bce4 libffi via submodule 5ddb307 Do not hardcode the specific linker to use 83dcaa8 [iserv] fix loadDLL b5ca082 We define the `_HOST_ARCH` to `1`, but never to `0`in 094a752 Fix iossimulator 6ef6e7c Drop custom apple handling 418bcf7 bump config.{guess,sub} 1345c7c Pass LLVMTarget (identical to --target) c0872bf Use NEED_PTHREAD_LIB a67cfc7 Revert "libffi via submodule" 2316ee1 Add regression test for #12850 6f99923 pmCheck: Don't generate PmId OccNames from Uniques 1381c14 Fix incorrect ambiguity error on identically-named data constructors 2fcb5c5 compiler: Do not look up fail in RnExpr if bind pattern is irrefutible. aa8dcb3 rts: Don't build StgCRunAsm.S if unregisterised 6e890e8 Add Outputable instance for Node 1f770a5 Use Proxy rather than undefined in MatchLit 2277172 Parenthesize pretty-printed equalities when necessary eaf9cc4 Fix collect_lpat's treatment of HsSplicedPats 01db135 Allow spliced patterns in pattern synonyms b9d1dae users-guide: Document requirement of at least one -dep-suffix 06d2a50 Update autoconf scripts 3e79fe4 Fix up tests for #13594 3760303 testsuite: Fix location of T13594 test a3873e8 RnEnv refactoring 410906b Update autoconf scripts from correct source 09938f2 Typos [ci skip] 01af8ae Add regression tests for #12083 ba5114e Add regression test for #11966 a13adcf Add regression test for #11964 ab91daf Automatically add SCCs to INLINABLE bindings 1edee7a Fix crash in isModuleInterpreted for HsBoot (fixes #13591) c068c38 Render \t as 8 spaces in caret diagnostics 8fd7442 Bump haddock submodule 3032ae8 Revert "Treat banged bindings as FunBinds" 947b294 Testing simpler Jenkinsfile 38cc04e Testing From git at git.haskell.org Sat May 13 20:09:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 13 May 2017 20:09:15 +0000 (UTC) Subject: [commit: ghc] master: Add a test for #11272 (70191f5) Message-ID: <20170513200915.95CF83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/70191f59dd8990c6b1917954a087f4fad67e9c4f/ghc >--------------------------------------------------------------- commit 70191f59dd8990c6b1917954a087f4fad67e9c4f Author: David Feuer Date: Sat May 13 16:09:31 2017 -0400 Add a test for #11272 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #11272 Differential Revision: https://phabricator.haskell.org/D3561 >--------------------------------------------------------------- 70191f59dd8990c6b1917954a087f4fad67e9c4f testsuite/tests/simplCore/should_compile/Makefile | 7 +++++++ testsuite/tests/simplCore/should_compile/T11272.hs | 7 +++++++ testsuite/tests/simplCore/should_compile/T11272a.hs | 10 ++++++++++ testsuite/tests/simplCore/should_compile/all.T | 4 ++++ 4 files changed, 28 insertions(+) diff --git a/testsuite/tests/simplCore/should_compile/Makefile b/testsuite/tests/simplCore/should_compile/Makefile index 779e7f2..a01edb2 100644 --- a/testsuite/tests/simplCore/should_compile/Makefile +++ b/testsuite/tests/simplCore/should_compile/Makefile @@ -218,3 +218,10 @@ str-rules: .PHONY: T13340 T13340: '$(TEST_HC)' $(TEST_HC_OPTS) -c -O T13340.hs -ddump-simpl -dsuppress-all | grep -c '\+#' + + +# We expect to see all dictionaries specialized away. +.PHONY: T11272 +T11272: + '$(TEST_HC)' $(TEST_HC_OPTS) -c -O T11272a.hs + '$(TEST_HC)' $(TEST_HC_OPTS) -c -O -ddump-prep T11272.hs | { ! grep Ord ;} diff --git a/testsuite/tests/simplCore/should_compile/T11272.hs b/testsuite/tests/simplCore/should_compile/T11272.hs new file mode 100644 index 0000000..d78ee15 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T11272.hs @@ -0,0 +1,7 @@ +module T11272 where + +import T11272a as A +import Control.Monad.Trans.State + +specialised :: Int -> Int -> () +specialised x y = execState (A.overloaded x y) () diff --git a/testsuite/tests/simplCore/should_compile/T11272a.hs b/testsuite/tests/simplCore/should_compile/T11272a.hs new file mode 100644 index 0000000..19c9cd2 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T11272a.hs @@ -0,0 +1,10 @@ +module T11272a where + +import Control.Monad.Trans.State +import Control.Monad + +overloaded :: Ord a => a -> a -> State () () +overloaded x y = do + () <- get + when (x <= y) (overloaded y x) +{-# INLINABLE overloaded #-} diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index 1b45930..1af5cbe 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -260,3 +260,7 @@ test('T13468', run_command, ['$MAKE -s --no-print-directory T13468']) test('T13543', normal, compile, ['-ddump-str-signatures']) +test('T11272', + normal, + run_command, + ['$MAKE -s --no-print-directory T11272']) From git at git.haskell.org Sat May 13 23:26:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 13 May 2017 23:26:37 +0000 (UTC) Subject: [commit: ghc] master: Add a test for #12600 (56de222) Message-ID: <20170513232637.8DD7E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/56de2225fa5d22f38b93489a03d5c8b7301b759e/ghc >--------------------------------------------------------------- commit 56de2225fa5d22f38b93489a03d5c8b7301b759e Author: David Feuer Date: Sat May 13 19:26:59 2017 -0400 Add a test for #12600 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #12600 Differential Revision: https://phabricator.haskell.org/D3580 >--------------------------------------------------------------- 56de2225fa5d22f38b93489a03d5c8b7301b759e testsuite/tests/simplCore/should_compile/Makefile | 5 ++++ testsuite/tests/simplCore/should_compile/T12600.hs | 29 ++++++++++++++++++++++ .../tests/simplCore/should_compile/T12600.stdout | 1 + testsuite/tests/simplCore/should_compile/all.T | 4 +++ 4 files changed, 39 insertions(+) diff --git a/testsuite/tests/simplCore/should_compile/Makefile b/testsuite/tests/simplCore/should_compile/Makefile index a01edb2..f56a851 100644 --- a/testsuite/tests/simplCore/should_compile/Makefile +++ b/testsuite/tests/simplCore/should_compile/Makefile @@ -225,3 +225,8 @@ T13340: T11272: '$(TEST_HC)' $(TEST_HC_OPTS) -c -O T11272a.hs '$(TEST_HC)' $(TEST_HC_OPTS) -c -O -ddump-prep T11272.hs | { ! grep Ord ;} + +# We expect to see a $wfoo worker that doesn't take any dictionaries. +.PHONY: T12600 +T12600: + '$(TEST_HC)' $(TEST_HC_OPTS) -c -O -ddump-prep -dsuppress-all -dsuppress-uniques -dno-suppress-type-signatures -dppr-cols=200 T12600.hs | grep "wfoo" | head -n 1 diff --git a/testsuite/tests/simplCore/should_compile/T12600.hs b/testsuite/tests/simplCore/should_compile/T12600.hs new file mode 100644 index 0000000..d08d923 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T12600.hs @@ -0,0 +1,29 @@ +module T12600 where + +-- We don't want to see any dictionary-passing in foo. Everything +-- should be inlined or specialized away. + +class Eq1 f where + eq1 :: Eq a => f a -> f a -> Bool + +data F a = F !a !a +data G f a = G !(f a) !(f a) + +instance Eq1 F where + eq1 = \(F a b) (F c d) -> + -- In order to reproduce the problem, the body of this function needs to be + -- large enough to prevent GHC from voluntarily inlining it. + larger $ larger $ larger $ larger $ larger $ larger $ + a == c && b == d + {-# INLINE eq1 #-} + +larger :: a -> a +larger = id +{-# NOINLINE larger #-} + +instance (Eq1 f) => Eq1 (G f) where + eq1 = \(G a b) (G c d) -> eq1 a c && eq1 b d + {-# INLINE eq1 #-} + +foo :: G F Int -> G F Int -> Bool +foo a b = eq1 a b diff --git a/testsuite/tests/simplCore/should_compile/T12600.stdout b/testsuite/tests/simplCore/should_compile/T12600.stdout new file mode 100644 index 0000000..9411874 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T12600.stdout @@ -0,0 +1 @@ +$wfoo :: Int# -> Int# -> Int# -> Int# -> Int# -> Int# -> Int# -> Int# -> Bool diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index 1af5cbe..b8a0c66 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -264,3 +264,7 @@ test('T11272', normal, run_command, ['$MAKE -s --no-print-directory T11272']) +test('T12600', + normal, + run_command, + ['$MAKE -s --no-print-directory T12600']) From git at git.haskell.org Sun May 14 09:34:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 May 2017 09:34:31 +0000 (UTC) Subject: [commit: ghc] master: includes/Stg.h: '#if sparch_HOST_ARCH' -> '#if defined(sparch_HOST_ARCH)' (1269aff) Message-ID: <20170514093431.6EC503A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1269aff19e7b7114dc2cf995560e7e2042d07d1c/ghc >--------------------------------------------------------------- commit 1269aff19e7b7114dc2cf995560e7e2042d07d1c Author: Sergei Trofimovich Date: Sun May 14 09:17:37 2017 +0100 includes/Stg.h: '#if sparch_HOST_ARCH' -> '#if defined(sparch_HOST_ARCH)' Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 1269aff19e7b7114dc2cf995560e7e2042d07d1c includes/Stg.h | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/includes/Stg.h b/includes/Stg.h index df71e4e..f377e50 100644 --- a/includes/Stg.h +++ b/includes/Stg.h @@ -360,7 +360,7 @@ INLINE_HEADER StgDouble PK_DBL (W_ p_src[]) { return *(StgDou * independently - unfortunately this code isn't writable in C, we * have to use inline assembler. */ -#if sparc_HOST_ARCH +#if defined(sparc_HOST_ARCH) #define ASSIGN_DBL(dst0,src) \ { StgPtr dst = (StgPtr)(dst0); \ From git at git.haskell.org Sun May 14 14:35:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 May 2017 14:35:13 +0000 (UTC) Subject: [commit: ghc] master: Update unix submodule (2a971e3) Message-ID: <20170514143513.081B73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2a971e35d96613183c6ebc81e1bd274b65cb0a1f/ghc >--------------------------------------------------------------- commit 2a971e35d96613183c6ebc81e1bd274b65cb0a1f Author: Ben Gamari Date: Sat May 13 21:19:45 2017 -0400 Update unix submodule >--------------------------------------------------------------- 2a971e35d96613183c6ebc81e1bd274b65cb0a1f libraries/unix | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/unix b/libraries/unix index 19aaa0f..eb5fc94 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit 19aaa0fcca3427e4006a967972eb16a570ca43b1 +Subproject commit eb5fc942f8f570e754bba0f57a8fdaec3400194f From git at git.haskell.org Sun May 14 19:34:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 May 2017 19:34:42 +0000 (UTC) Subject: [commit: ghc] master: rts: annotate switch/case with '/* fallthrough */' (230416f) Message-ID: <20170514193442.B45DC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/230416f8b6f6731064115a2905ad354e27b7d605/ghc >--------------------------------------------------------------- commit 230416f8b6f6731064115a2905ad354e27b7d605 Author: Sergei Trofimovich Date: Sun May 14 20:22:37 2017 +0100 rts: annotate switch/case with '/* fallthrough */' Fixes gcc-7.1.0 warnings of form: rts/sm/Scav.c:559:9: error: error: this statement may fall through [-Werror=implicit-fallthrough=] scavenge_fun_srt(info); ^~~~~~~~~~~~~~~~~~~~~~ Many of places are indeed unobvious and some are already annotated by comments. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 230416f8b6f6731064115a2905ad354e27b7d605 rts/RaiseAsync.c | 1 + rts/sm/CNF.c | 6 ++++++ rts/sm/MarkWeak.c | 1 + rts/sm/Sanity.c | 1 + rts/sm/Scav.c | 4 ++++ 5 files changed, 13 insertions(+) diff --git a/rts/RaiseAsync.c b/rts/RaiseAsync.c index 31cc915..e04a875 100644 --- a/rts/RaiseAsync.c +++ b/rts/RaiseAsync.c @@ -459,6 +459,7 @@ check_target: // fall to next } #endif + /* fallthrough */ case BlockedOnCCall: blockedThrowTo(cap,target,msg); return THROWTO_BLOCKED; diff --git a/rts/sm/CNF.c b/rts/sm/CNF.c index f740d05..bdb018d 100644 --- a/rts/sm/CNF.c +++ b/rts/sm/CNF.c @@ -689,14 +689,17 @@ verify_consistency_block (StgCompactNFData *str, StgCompactNFDataBlock *block) switch (info->type) { case CONSTR_1_0: check_object_in_compact(str, UNTAG_CLOSURE(q->payload[0])); + /* fallthrough */ case CONSTR_0_1: p += sizeofW(StgClosure) + 1; break; case CONSTR_2_0: check_object_in_compact(str, UNTAG_CLOSURE(q->payload[1])); + /* fallthrough */ case CONSTR_1_1: check_object_in_compact(str, UNTAG_CLOSURE(q->payload[0])); + /* fallthrough */ case CONSTR_0_2: p += sizeofW(StgClosure) + 2; break; @@ -928,6 +931,7 @@ fixup_block(StgCompactNFDataBlock *block, StgWord *fixup_table, uint32_t count) if (!fixup_one_pointer(fixup_table, count, &((StgClosure*)p)->payload[0])) return false; + /* fallthrough */ case CONSTR_0_1: p += sizeofW(StgClosure) + 1; break; @@ -936,10 +940,12 @@ fixup_block(StgCompactNFDataBlock *block, StgWord *fixup_table, uint32_t count) if (!fixup_one_pointer(fixup_table, count, &((StgClosure*)p)->payload[1])) return false; + /* fallthrough */ case CONSTR_1_1: if (!fixup_one_pointer(fixup_table, count, &((StgClosure*)p)->payload[0])) return false; + /* fallthrough */ case CONSTR_0_2: p += sizeofW(StgClosure) + 2; break; diff --git a/rts/sm/MarkWeak.c b/rts/sm/MarkWeak.c index c7a87a2..691e56a 100644 --- a/rts/sm/MarkWeak.c +++ b/rts/sm/MarkWeak.c @@ -155,6 +155,7 @@ traverseWeakPtrList(void) // otherwise, fall through... } + /* fallthrough */ case WeakPtrs: { diff --git a/rts/sm/Sanity.c b/rts/sm/Sanity.c index 6bfa1cb..53b1010 100644 --- a/rts/sm/Sanity.c +++ b/rts/sm/Sanity.c @@ -102,6 +102,7 @@ checkStackFrame( StgPtr c ) case UPDATE_FRAME: ASSERT(LOOKS_LIKE_CLOSURE_PTR(((StgUpdateFrame*)c)->updatee)); + /* fallthrough */ case ATOMICALLY_FRAME: case CATCH_RETRY_FRAME: case CATCH_STM_FRAME: diff --git a/rts/sm/Scav.c b/rts/sm/Scav.c index ab7b69f..d26a893 100644 --- a/rts/sm/Scav.c +++ b/rts/sm/Scav.c @@ -557,6 +557,7 @@ scavenge_block (bdescr *bd) case FUN_1_0: scavenge_fun_srt(info); + /* fallthrough */ case CONSTR_1_0: evacuate(&((StgClosure *)p)->payload[0]); p += sizeofW(StgHeader) + 1; @@ -569,6 +570,7 @@ scavenge_block (bdescr *bd) case FUN_0_1: scavenge_fun_srt(info); + /* fallthrough */ case CONSTR_0_1: p += sizeofW(StgHeader) + 1; break; @@ -580,6 +582,7 @@ scavenge_block (bdescr *bd) case FUN_0_2: scavenge_fun_srt(info); + /* fallthrough */ case CONSTR_0_2: p += sizeofW(StgHeader) + 2; break; @@ -592,6 +595,7 @@ scavenge_block (bdescr *bd) case FUN_1_1: scavenge_fun_srt(info); + /* fallthrough */ case CONSTR_1_1: evacuate(&((StgClosure *)p)->payload[0]); p += sizeofW(StgHeader) + 2; From git at git.haskell.org Sun May 14 19:34:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 May 2017 19:34:45 +0000 (UTC) Subject: [commit: ghc] master: ProfilerReportJson.c: fix out-of-bounds access (20c39b7) Message-ID: <20170514193445.6C1503A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/20c39b7743a242fce785e5c6507a8549dba7a8d2/ghc >--------------------------------------------------------------- commit 20c39b7743a242fce785e5c6507a8549dba7a8d2 Author: Sergei Trofimovich Date: Sun May 14 20:21:50 2017 +0100 ProfilerReportJson.c: fix out-of-bounds access Found by gcc-7.1 which reported build error as: rts/ProfilerReportJson.c:23:16: error: error: comparison between pointer and zero character constant [-Werror=pointer-compare] for (; str != '\0' && len > 0; str++) { ^~ | 23 | for (; str != '\0' && len > 0; str++) { | ^ Unfixed code in context: ```c static void escapeString(char const* str, char *out, int len) { len--; // reserve character in output for terminating NUL for (; str != '\0' && len > 0; str++) { char c = *str; ``` The intent here is to process 'len' (if positive) or '\0'-terminator in 'str' but dereference was missing. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 20c39b7743a242fce785e5c6507a8549dba7a8d2 rts/ProfilerReportJson.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/ProfilerReportJson.c b/rts/ProfilerReportJson.c index 3cf875e..a786921 100644 --- a/rts/ProfilerReportJson.c +++ b/rts/ProfilerReportJson.c @@ -20,7 +20,7 @@ static void escapeString(char const* str, char *out, int len) { len--; // reserve character in output for terminating NUL - for (; str != '\0' && len > 0; str++) { + for (; *str != '\0' && len > 0; str++) { char c = *str; if (c == '\\') { if (len < 2) break; From git at git.haskell.org Sun May 14 19:34:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 May 2017 19:34:48 +0000 (UTC) Subject: [commit: ghc] master: rts/linker/ElfTypes.h: restore powerps (and others) support (d5414dd) Message-ID: <20170514193448.276DF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d5414dd61b540be3b3945c321065a1c70c7962ac/ghc >--------------------------------------------------------------- commit d5414dd61b540be3b3945c321065a1c70c7962ac Author: Sergei Trofimovich Date: Sun May 14 20:33:16 2017 +0100 rts/linker/ElfTypes.h: restore powerps (and others) support GHC build fails for powerpc-unknown-linux-gnu and hppa-unknown-linux-gnu targets as: rts_dist_HC rts/dist/build/RtsStartup.o rts/linker/ElfTypes.h:23:4: error: error: #error "Unsupported arch!" Before the change code tried to whitelist architectures and classify them into ELF32/ELF64. It does not work for UNREG arches like 'hppa', 'sparc64', 'm68k', 'mips'. It is nuanced for things like mips64 and x86_64: 'mips64-unknown-linux-gnu-gcc -mabi=64' is ELFCLASS64 'mips64-unknown-linux-gnu-gcc' is ELFCLASS32 'x86_64-pc-linux-gnu-gcc' is ELFCLASS64 'x86_64-pc-linux-gnu-gcc -mx32' is ELFCLASS32 Here it's not enough to know HOST_ARCH. We really need to know ABI. The change uses '__LP64__' as a proxy for ELFCLASS64. Signed-off-by: Sergei Trofimovich Reviewers: angerman, simonmar, austin, bgamari, erikd Reviewed By: angerman, bgamari, erikd Subscribers: rwbarton, thomie GHC Trac Issues: #13696 Differential Revision: https://phabricator.haskell.org/D3583 >--------------------------------------------------------------- d5414dd61b540be3b3945c321065a1c70c7962ac rts/linker/ElfTypes.h | 11 ++++------- 1 file changed, 4 insertions(+), 7 deletions(-) diff --git a/rts/linker/ElfTypes.h b/rts/linker/ElfTypes.h index 2f34d4a..ca5bc58 100644 --- a/rts/linker/ElfTypes.h +++ b/rts/linker/ElfTypes.h @@ -12,15 +12,12 @@ */ # define ELF_TARGET_AMD64 /* Used inside on Solaris 11 */ -#if defined(powerpc64_HOST_ARCH) || defined(powerpc64le_HOST_ARCH) \ - || defined(ia64_HOST_ARCH) || defined(aarch64_HOST_ARCH) \ - || defined(x86_64_HOST_ARCH) + +/* __LP64__ is a rough proxy if a platform is ELFCLASS64 */ +#if defined(__LP64__) || defined(_LP64) # define ELF_64BIT -#elif defined(sparc_HOST_ARCH) || defined(i386_HOST_ARCH) \ - || defined(arm_HOST_ARCH) -# define ELF_32BIT #else -# error "Unsupported arch!" +# define ELF_32BIT #endif #if defined(ELF_64BIT) From git at git.haskell.org Mon May 15 11:15:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 May 2017 11:15:14 +0000 (UTC) Subject: [commit: ghc] master: Stress test for nested module hierarchies (e527fc2) Message-ID: <20170515111514.C06AA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e527fc2e90958280a36645b6bd0223861cc50a55/ghc >--------------------------------------------------------------- commit e527fc2e90958280a36645b6bd0223861cc50a55 Author: Bartosz Nitka Date: Mon May 15 04:14:01 2017 -0700 Stress test for nested module hierarchies I'm optimizing a case that is well approximated by multiple layers of modules where every module in a layer imports all the modules in the layer below. It turns out I regressed performance on such cases in 7fea7121. I'm adding a test case to track improvements and prevent future regressions. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Reviewed By: simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3575 >--------------------------------------------------------------- e527fc2e90958280a36645b6bd0223861cc50a55 compiler/deSugar/DsUsage.hs | 4 ++-- compiler/iface/MkIface.hs | 5 ++--- compiler/typecheck/TcRnDriver.hs | 14 ++++++------- compiler/typecheck/TcRnTypes.hs | 24 ++++++++++++++-------- testsuite/tests/perf/compiler/all.T | 12 +++++++++++ testsuite/tests/perf/compiler/genMultiLayerModules | 21 +++++++++++++++++++ 6 files changed, 60 insertions(+), 20 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 e527fc2e90958280a36645b6bd0223861cc50a55 From git at git.haskell.org Mon May 15 11:23:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 May 2017 11:23:08 +0000 (UTC) Subject: [commit: ghc] master: Revert "Stress test for nested module hierarchies" (06ad87e) Message-ID: <20170515112308.DAC6F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/06ad87ef0cc77af05693916decbed72a54906e3f/ghc >--------------------------------------------------------------- commit 06ad87ef0cc77af05693916decbed72a54906e3f Author: Bartosz Nitka Date: Mon May 15 04:21:52 2017 -0700 Revert "Stress test for nested module hierarchies" This reverts commit e527fc2e90958280a36645b6bd0223861cc50a55. I merged more than I intended in e527fc2e, I will merge D3575 and D3577 separately. >--------------------------------------------------------------- 06ad87ef0cc77af05693916decbed72a54906e3f compiler/deSugar/DsUsage.hs | 4 ++-- compiler/iface/MkIface.hs | 5 +++-- compiler/typecheck/TcRnDriver.hs | 14 ++++++------- compiler/typecheck/TcRnTypes.hs | 24 ++++++++-------------- testsuite/tests/perf/compiler/all.T | 12 ----------- testsuite/tests/perf/compiler/genMultiLayerModules | 21 ------------------- 6 files changed, 20 insertions(+), 60 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 06ad87ef0cc77af05693916decbed72a54906e3f From git at git.haskell.org Mon May 15 11:41:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 May 2017 11:41:49 +0000 (UTC) Subject: [commit: ghc] master: Stress test for nested module hierarchies (ffbcfff) Message-ID: <20170515114149.8A7913A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ffbcffffecf0307ff4dd3173503e2d3387d53386/ghc >--------------------------------------------------------------- commit ffbcffffecf0307ff4dd3173503e2d3387d53386 Author: Bartosz Nitka Date: Fri May 12 06:38:18 2017 -0700 Stress test for nested module hierarchies I'm optimizing a case that is well approximated by multiple layers of modules where every module in a layer imports all the modules in the layer below. It turns out I regressed performance on such cases in 7fea7121. I'm adding a test case to track improvements and prevent future regressions. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3575 >--------------------------------------------------------------- ffbcffffecf0307ff4dd3173503e2d3387d53386 testsuite/tests/perf/compiler/all.T | 11 +++++++++++ testsuite/tests/perf/compiler/genMultiLayerModules | 21 +++++++++++++++++++++ 2 files changed, 32 insertions(+) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 360bef4..28e1465 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -1096,3 +1096,14 @@ test('T13379', ], compile, ['']) + +test('MultiLayerModules', + [ compiler_stats_num_field('bytes allocated', + [(wordsize(64), 12139116496, 10), + # initial: 12139116496 + ]), + pre_cmd('./genMultiLayerModules'), + extra_files(['genMultiLayerModules']), + ], + multimod_compile, + ['MultiLayerModules', '-v0']) diff --git a/testsuite/tests/perf/compiler/genMultiLayerModules b/testsuite/tests/perf/compiler/genMultiLayerModules new file mode 100755 index 0000000..b98c481 --- /dev/null +++ b/testsuite/tests/perf/compiler/genMultiLayerModules @@ -0,0 +1,21 @@ +#!/bin/bash +# Generate $DEPTH layers of modules with $WIDTH modules on each layer +# Every module on layer N imports all the modules on layer N-1 +# MultiLayerModules.hs imports all the modules from the last layer +DEPTH=15 +WIDTH=40 +for i in $(seq -w 1 $WIDTH); do + echo "module DummyLevel0M$i where" > DummyLevel0M$i.hs; +done +for l in $(seq 1 $DEPTH); do + for i in $(seq -w 1 $WIDTH); do + echo "module DummyLevel${l}M$i where" > DummyLevel${l}M$i.hs; + for j in $(seq -w 1 $WIDTH); do + echo "import DummyLevel$((l-1))M$j" >> DummyLevel${l}M$i.hs; + done + done +done +echo "module MultiLayerModules where" > MultiLayerModules.hs +for j in $(seq -w 1 $WIDTH); do + echo "import DummyLevel${DEPTH}M$j" >> MultiLayerModules.hs; +done From git at git.haskell.org Mon May 15 11:46:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 May 2017 11:46:01 +0000 (UTC) Subject: [commit: ghc] master: Revert "Use a deterministic map for imp_dep_mods" (8bf50d5) Message-ID: <20170515114601.A22033A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8bf50d5026f92eb5a6768eb2ac38479802da1411/ghc >--------------------------------------------------------------- commit 8bf50d5026f92eb5a6768eb2ac38479802da1411 Author: Bartosz Nitka Date: Mon May 15 04:44:35 2017 -0700 Revert "Use a deterministic map for imp_dep_mods" This reverts commit 7fea7121ce195e562a5443c0a8ef3861504ef1b3. It turns out that on a newly added MultiLayerModules test case it gets very expensive to union the transitive module sets while preserving determinism. Fortunately, we can just sort to restore determinism when converting imp_dep_mods to a list. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3577 >--------------------------------------------------------------- 8bf50d5026f92eb5a6768eb2ac38479802da1411 compiler/deSugar/DsUsage.hs | 4 ++-- compiler/iface/MkIface.hs | 5 ++--- compiler/typecheck/TcRnDriver.hs | 14 +++++++------- compiler/typecheck/TcRnTypes.hs | 24 ++++++++++++++++-------- testsuite/tests/perf/compiler/all.T | 3 ++- 5 files changed, 29 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 8bf50d5026f92eb5a6768eb2ac38479802da1411 From git at git.haskell.org Mon May 15 22:12:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 May 2017 22:12:24 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Document -g flag (bc06655) Message-ID: <20170515221224.174713A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bc066558e83bfa741a58ec1797ac8fccc507266e/ghc >--------------------------------------------------------------- commit bc066558e83bfa741a58ec1797ac8fccc507266e Author: Ben Gamari Date: Mon May 15 14:21:38 2017 -0400 users-guide: Document -g flag >--------------------------------------------------------------- bc066558e83bfa741a58ec1797ac8fccc507266e docs/users_guide/debug-info.rst | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/docs/users_guide/debug-info.rst b/docs/users_guide/debug-info.rst index 613936d..2f192f2 100644 --- a/docs/users_guide/debug-info.rst +++ b/docs/users_guide/debug-info.rst @@ -5,13 +5,14 @@ Since the 7.10 release GHC can emit a debugging information to help debugging tools understand the code that GHC produces. This debugging information is useable by most UNIX debugging tools. -.. warning:: +.. ghc-flag:: -g, -g - This feature is still in technology preview state. There are known cases - where requesting a stack-trace can cause your program to segmentation fault - (e.g. :ghc-ticket:`11353`, :ghc-ticket:`11338`, and :ghc-ticket:`11337`). - Consequently, we can not recommend that stack trace support be used in - production code. + :since: 7.10, numeric levels since 8.0 + + Emit debug information in object code. Currently only DWARF debug + information is supported on x86-64 and i386. Currently debug levels 0 + through 3 are accepted, with 0 disabling debug information production. + Levels 1 through 3 are functionally equivalent. Tutorial From git at git.haskell.org Mon May 15 22:12:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 May 2017 22:12:27 +0000 (UTC) Subject: [commit: ghc] master: Print warnings on parser failures (#12610). (49012eb) Message-ID: <20170515221227.A8A0E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/49012ebc9ed44a0b1f8de3781e15c8115d3074f8/ghc >--------------------------------------------------------------- commit 49012ebc9ed44a0b1f8de3781e15c8115d3074f8 Author: Dave Laing Date: Mon May 15 16:09:11 2017 -0400 Print warnings on parser failures (#12610). Test Plan: validate Reviewers: austin, bgamari, simonmar, mpickering Reviewed By: mpickering Subscribers: mpickering, rwbarton, thomie GHC Trac Issues: #12610 Differential Revision: https://phabricator.haskell.org/D3584 >--------------------------------------------------------------- 49012ebc9ed44a0b1f8de3781e15c8115d3074f8 compiler/backpack/DriverBkp.hs | 2 +- compiler/cmm/CmmMonad.hs | 2 +- compiler/cmm/CmmParse.y | 6 ++-- compiler/main/GHC.hs | 13 ++++---- compiler/main/HeaderInfo.hs | 4 ++- compiler/main/HscMain.hs | 8 +++-- compiler/main/InteractiveEval.hs | 8 ++--- compiler/parser/Lexer.x | 40 ++++++++++++++++-------- testsuite/tests/parser/should_fail/T12610.hs | 6 ++++ testsuite/tests/parser/should_fail/T12610.stderr | 6 ++++ testsuite/tests/parser/should_fail/all.T | 3 +- 11 files changed, 67 insertions(+), 31 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 49012ebc9ed44a0b1f8de3781e15c8115d3074f8 From git at git.haskell.org Tue May 16 01:08:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 01:08:45 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add testcase for T13658 (efd113f) Message-ID: <20170516010845.B6EE13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/efd113f72f07908e57c62cbce71f8d4a1e1d2819/ghc >--------------------------------------------------------------- commit efd113f72f07908e57c62cbce71f8d4a1e1d2819 Author: Ben Gamari Date: Mon May 15 20:15:11 2017 -0400 testsuite: Add testcase for T13658 >--------------------------------------------------------------- efd113f72f07908e57c62cbce71f8d4a1e1d2819 testsuite/tests/simplCore/should_compile/T13658.hs | 39 ++++++++++++++++++++++ testsuite/tests/simplCore/should_compile/all.T | 1 + 2 files changed, 40 insertions(+) diff --git a/testsuite/tests/simplCore/should_compile/T13658.hs b/testsuite/tests/simplCore/should_compile/T13658.hs new file mode 100644 index 0000000..0890e89 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T13658.hs @@ -0,0 +1,39 @@ +{-# LANGUAGE TypeInType #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE BangPatterns #-} + +{- # OPTIONS_GHC -Werror #-} +{-# OPTIONS_GHC -g -O2 #-} + +module Bug (bug) where + +-- import GHC.Base (seq) +import Unsafe.Coerce (unsafeCoerce) + +undefined :: a +undefined = undefined + +data TypeRep (a :: k) where + TrTyCon :: TypeRep (a :: k) + TrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1). + TypeRep (a b) + +data SomeTypeRep where + SomeTypeRep :: forall k (a :: k). + TypeRep a + -> SomeTypeRep + +mkTrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1). + TypeRep (a :: k1 -> k2) + -> TypeRep (a b) +mkTrApp TrTyCon = undefined +mkTrApp TrApp = undefined + +bug :: SomeTypeRep +-- bug = f x -- this works +bug = f (f x) + where x = SomeTypeRep TrTyCon + f :: SomeTypeRep -> SomeTypeRep + f (SomeTypeRep acc) = SomeTypeRep (mkTrApp (unsafeCoerce acc)) diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index b8a0c66..5ed520d 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -268,3 +268,4 @@ test('T12600', normal, run_command, ['$MAKE -s --no-print-directory T12600']) +test('T13658', normal, compile, ['-dcore-lint']) From git at git.haskell.org Tue May 16 01:11:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 01:11:50 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump unix submodule (eae4aaf) Message-ID: <20170516011150.AD4A83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/eae4aafc0b5ec8a6580693205681ed2007018ced/ghc >--------------------------------------------------------------- commit eae4aafc0b5ec8a6580693205681ed2007018ced Author: Ben Gamari Date: Thu May 11 12:30:54 2017 -0400 Bump unix submodule >--------------------------------------------------------------- eae4aafc0b5ec8a6580693205681ed2007018ced libraries/unix | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/unix b/libraries/unix index db8be85..eb5fc94 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit db8be857ba0d1e25e8d30c53ea7338cb9929b9b4 +Subproject commit eb5fc942f8f570e754bba0f57a8fdaec3400194f From git at git.haskell.org Tue May 16 01:11:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 01:11:56 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Parenthesize pretty-printed equalities when necessary (66d5e80) Message-ID: <20170516011156.D65573A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/66d5e8015bed91fd0e2091641fe855c433c24b6c/ghc >--------------------------------------------------------------- commit 66d5e8015bed91fd0e2091641fe855c433c24b6c Author: Ryan Scott Date: Thu May 11 15:42:55 2017 -0400 Parenthesize pretty-printed equalities when necessary Fixes #13677 by parenthesizing equalities in a sufficiently high pretty-printing context. Test Plan: make test TEST=T13677 Reviewers: goldfire, austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13677 Differential Revision: https://phabricator.haskell.org/D3570 (cherry picked from commit 2277172ac3ea0bbeddebc9999a5d8b5f9f58afc9) >--------------------------------------------------------------- 66d5e8015bed91fd0e2091641fe855c433c24b6c compiler/iface/IfaceType.hs | 2 +- mk/build.mk.sample | 4 +- rts/Libdw.c | 83 ++++++++++++++++++---- testsuite/tests/typecheck/should_fail/T13677.hs | 11 +++ .../tests/typecheck/should_fail/T13677.stderr | 4 ++ testsuite/tests/typecheck/should_fail/all.T | 1 + 6 files changed, 89 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 66d5e8015bed91fd0e2091641fe855c433c24b6c From git at git.haskell.org Tue May 16 01:11:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 01:11:53 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: users-guide: Document -g flag (b29a9f0) Message-ID: <20170516011153.634C03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/b29a9f0ea8c25fbf84d3afe0bab43a2d82bb1324/ghc >--------------------------------------------------------------- commit b29a9f0ea8c25fbf84d3afe0bab43a2d82bb1324 Author: Ben Gamari Date: Mon May 15 14:21:38 2017 -0400 users-guide: Document -g flag (cherry picked from commit bc066558e83bfa741a58ec1797ac8fccc507266e) >--------------------------------------------------------------- b29a9f0ea8c25fbf84d3afe0bab43a2d82bb1324 docs/users_guide/debug-info.rst | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/docs/users_guide/debug-info.rst b/docs/users_guide/debug-info.rst index 613936d..2f192f2 100644 --- a/docs/users_guide/debug-info.rst +++ b/docs/users_guide/debug-info.rst @@ -5,13 +5,14 @@ Since the 7.10 release GHC can emit a debugging information to help debugging tools understand the code that GHC produces. This debugging information is useable by most UNIX debugging tools. -.. warning:: +.. ghc-flag:: -g, -g - This feature is still in technology preview state. There are known cases - where requesting a stack-trace can cause your program to segmentation fault - (e.g. :ghc-ticket:`11353`, :ghc-ticket:`11338`, and :ghc-ticket:`11337`). - Consequently, we can not recommend that stack trace support be used in - production code. + :since: 7.10, numeric levels since 8.0 + + Emit debug information in object code. Currently only DWARF debug + information is supported on x86-64 and i386. Currently debug levels 0 + through 3 are accepted, with 0 disabling debug information production. + Levels 1 through 3 are functionally equivalent. Tutorial From git at git.haskell.org Tue May 16 01:11:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 01:11:59 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Render \t as 8 spaces in caret diagnostics (cd59db5) Message-ID: <20170516011159.8C91D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/cd59db5a0dfb3b26a615036bcfdfd1c35d1e5e1d/ghc >--------------------------------------------------------------- commit cd59db5a0dfb3b26a615036bcfdfd1c35d1e5e1d Author: Phil Ruffwind Date: Thu May 11 15:41:08 2017 -0400 Render \t as 8 spaces in caret diagnostics Test Plan: validate Reviewers: austin, bgamari, rwbarton Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13664 Differential Revision: https://phabricator.haskell.org/D3549 (cherry picked from commit c068c38727b7bd7a1a75495167f7470abb7bf866) >--------------------------------------------------------------- cd59db5a0dfb3b26a615036bcfdfd1c35d1e5e1d compiler/main/ErrUtils.hs | 10 +++++++--- testsuite/driver/testlib.py | 14 ++++++++++++-- testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs | 3 +++ .../tests/warnings/should_fail/CaretDiagnostics1.stderr | 8 ++++++++ testsuite/tests/warnings/should_fail/all.T | 15 ++++++++++++++- 5 files changed, 44 insertions(+), 6 deletions(-) diff --git a/compiler/main/ErrUtils.hs b/compiler/main/ErrUtils.hs index ded7085..d87d2b2 100644 --- a/compiler/main/ErrUtils.hs +++ b/compiler/main/ErrUtils.hs @@ -261,8 +261,6 @@ getCaretDiagnostic severity (RealSrcSpan span) = do rowStr = show row multiline = row /= srcSpanEndLine span - stripNewlines = filter (/= '\n') - caretDiagnostic Nothing = empty caretDiagnostic (Just srcLineWithNewline) = sdocWithDynFlags $ \ dflags -> @@ -280,7 +278,13 @@ getCaretDiagnostic severity (RealSrcSpan span) = do where - srcLine = stripNewlines srcLineWithNewline + fixWhitespace (i, c) + | c == '\n' = "" + -- show tabs in a device-independent manner #13664 + | c == '\t' = replicate (8 - i `mod` 8) ' ' + | otherwise = [c] + + srcLine = concat (map fixWhitespace (zip [0..] srcLineWithNewline)) start = srcSpanStartCol span - 1 end | multiline = length srcLine diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 1f08f5b..b730685 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -84,6 +84,8 @@ def setTestOpts( f ): # test('test001', expect_fail, compile, ['']) # # to expect failure for this test. +# +# type TestOpt = (name :: String, opts :: Object) -> IO () def normal( name, opts ): return; @@ -518,6 +520,12 @@ def normalise_errmsg_fun( *fs ): def _normalise_errmsg_fun( name, opts, *fs ): opts.extra_errmsg_normaliser = join_normalisers(opts.extra_errmsg_normaliser, fs) +def normalise_whitespace_fun(f): + return lambda name, opts: _normalise_whitespace_fun(name, opts, f) + +def _normalise_whitespace_fun(name, opts, f): + opts.whitespace_normaliser = f + def normalise_version_( *pkgs ): def normalise_version__( str ): return re.sub('(' + '|'.join(map(re.escape,pkgs)) + ')-[0-9.]+', @@ -622,7 +630,7 @@ def runTest(watcher, opts, name, func, args): test_common_work(watcher, name, opts, func, args) # name :: String -# setup :: TestOpts -> IO () +# setup :: [TestOpt] -> IO () def test(name, setup, func, args): global aloneTests global parallelTests @@ -1006,7 +1014,9 @@ def do_compile(name, way, should_fail, top_mod, extra_mods, extra_hc_opts, **kwa join_normalisers(getTestOpts().extra_errmsg_normaliser, normalise_errmsg), expected_stderr_file, actual_stderr_file, - whitespace_normaliser=normalise_whitespace): + whitespace_normaliser=getattr(getTestOpts(), + "whitespace_normaliser", + normalise_whitespace)): return failBecause('stderr mismatch') # no problems found, this test passed diff --git a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs index 6ecadf6..3ebb5ee 100644 --- a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs +++ b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs @@ -15,3 +15,6 @@ main = do fóo :: Int fóo = () + +tabby :: Int +tabby = () diff --git a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr index 68fbfa7..600b7c7 100644 --- a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr +++ b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr @@ -70,3 +70,11 @@ CaretDiagnostics1.hs:17:7-8: error: | 17 | fóo = () | ^^ + +CaretDiagnostics1.hs:20:17-18: error: + • Couldn't match expected type ‘Int’ with actual type ‘()’ + • In the expression: () + In an equation for ‘tabby’: tabby = () + | +20 | tabby = () + | ^^ diff --git a/testsuite/tests/warnings/should_fail/all.T b/testsuite/tests/warnings/should_fail/all.T index 71a7a97..73117a9 100644 --- a/testsuite/tests/warnings/should_fail/all.T +++ b/testsuite/tests/warnings/should_fail/all.T @@ -1,3 +1,16 @@ +import re + +def normalise_whitespace_carefully(s): + # Merge contiguous whitespace characters into a single space + # except on caret diagnostic lines + return '\n'.join(line + if re.match(r'\s*\d*\s*\|', line) + else ' '.join(w for w in line.split()) + for line in s.split('\n')) + test('WerrorFail', normal, compile_fail, ['']) -test('CaretDiagnostics1', normal, compile_fail, ['-fdiagnostics-show-caret -ferror-spans']) +test('CaretDiagnostics1', + [normalise_whitespace_fun(normalise_whitespace_carefully)], + compile_fail, + ['-fdiagnostics-show-caret -ferror-spans']) test('CaretDiagnostics2', normal, compile_fail, ['-fdiagnostics-show-caret']) From git at git.haskell.org Tue May 16 01:12:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 01:12:02 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Reset cc_pend_sc flag in dropDerivedCt (b6f73dd) Message-ID: <20170516011202.C83E93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/b6f73dd7bacec13a7a8898fb0843efc10d4405e5/ghc >--------------------------------------------------------------- commit b6f73dd7bacec13a7a8898fb0843efc10d4405e5 Author: Simon Peyton Jones Date: Tue May 9 09:29:44 2017 +0100 Reset cc_pend_sc flag in dropDerivedCt I'd forgotten to reset this flag to True when dropping Derived constraints, which led to Trac #13662. Easily fixed. (cherry picked from commit 43a31683acbe2f8120fbb73fe5a6fd1f5de9db80) >--------------------------------------------------------------- b6f73dd7bacec13a7a8898fb0843efc10d4405e5 compiler/typecheck/TcCanonical.hs | 25 ++++++++----- compiler/typecheck/TcRnTypes.hs | 41 +++++++++++++++------- .../tests/indexed-types/should_compile/T13662.hs | 25 +++++++++++++ testsuite/tests/indexed-types/should_compile/all.T | 1 + 4 files changed, 72 insertions(+), 20 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 10f871f..b623541 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -161,18 +161,19 @@ canClass ev cls tys pend_sc ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We need to add superclass constraints for two reasons: -* For givens, they give us a route to to proof. E.g. +* For givens [G], they give us a route to to proof. E.g. f :: Ord a => a -> Bool f x = x == x We get a Wanted (Eq a), which can only be solved from the superclass of the Given (Ord a). -* For wanteds, they may give useful functional dependencies. E.g. +* For wanteds [W], and deriveds [WD], [D], they may give useful + functional dependencies. E.g. class C a b | a -> b where ... class C a b => D a b where ... - Now a Wanted constraint (D Int beta) has (C Int beta) as a superclass + Now a [W] constraint (D Int beta) has (C Int beta) as a superclass and that might tell us about beta, via C's fundeps. We can get this - by generateing a Derived (C Int beta) constraint. It's derived because + by generating a [D] (C Int beta) constraint. It's derived because we don't actually have to cough up any evidence for it; it's only there to generate fundep equalities. @@ -227,12 +228,20 @@ So here's the plan: 4. Go round to (2) again. This loop (2,3,4) is implemented in TcSimplify.simpl_loop. -We try to terminate the loop by flagging which class constraints -(given or wanted) are potentially un-expanded. This is what the -cc_pend_sc flag is for in CDictCan. So in Step 3 we only expand -superclasses for constraints with cc_pend_sc set to true (i.e. +The cc_pend_sc flag in a CDictCan records whether the superclasses of +this constraint have been expanded. Specifically, in Step 3 we only +expand superclasses for constraints with cc_pend_sc set to true (i.e. isPendingScDict holds). +Why do we do this? Two reasons: + +* To avoid repeated work, by repeatedly expanding the superclasses of + same constraint, + +* To terminate the above loop, at least in the -XNoRecursiveSuperClasses + case. If there are recursive superclasses we could, in principle, + expand forever, always encountering new constraints. + When we take a CNonCanonical or CIrredCan, but end up classifying it as a CDictCan, we set the cc_pend_sc flag to False. diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index ee4a6ef..927cac6 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -1493,14 +1493,14 @@ data Ct -- Atomic canonical constraints = CDictCan { -- e.g. Num xi cc_ev :: CtEvidence, -- See Note [Ct/evidence invariant] + cc_class :: Class, - cc_tyargs :: [Xi], -- cc_tyargs are function-free, hence Xi - cc_pend_sc :: Bool -- True <=> (a) cc_class has superclasses - -- (b) we have not (yet) added those - -- superclasses as Givens - -- NB: cc_pend_sc is used for G/W/D. For W/D the reason - -- we need superclasses is to expose possible improvement - -- via fundeps + cc_tyargs :: [Xi], -- cc_tyargs are function-free, hence Xi + + cc_pend_sc :: Bool -- See Note [The superclass story] in TcCanonical + -- True <=> (a) cc_class has superclasses + -- (b) we have not (yet) added those + -- superclasses as Givens } | CIrredEvCan { -- These stand for yet-unusable predicates @@ -1578,9 +1578,8 @@ holeOcc :: Hole -> OccName holeOcc (ExprHole uv) = unboundVarOcc uv holeOcc (TypeHole occ) = occ -{- -Note [Hole constraints] -~~~~~~~~~~~~~~~~~~~~~~~ +{- Note [Hole constraints] +~~~~~~~~~~~~~~~~~~~~~~~~~~ CHoleCan constraints are used for two kinds of holes, distinguished by cc_hole: @@ -1775,13 +1774,25 @@ 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 + 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 } + ct' = setPendingScDict ct -- See Note [Resetting cc_pend_sc] + +{- Note [Resetting cc_pend_sc] +~~~~~~~~~~~~~~~~~~~~~~~~~~~ +When we discard Derived constraints, in dropDerivedSimples, we must +set the cc_pend_sc flag to True, so that if we re-process this +CDictCan we will re-generate its derived superclasses. Otherwise +we might miss some fundeps. Trac #13662 showed this up. + +See Note [The superclass story] in TcCanonical. +-} + dropDerivedInsols :: Cts -> Cts -- See Note [Dropping derived constraints] @@ -1976,6 +1987,12 @@ isPendingScDict ct@(CDictCan { cc_pend_sc = True }) = Just (ct { cc_pend_sc = False }) isPendingScDict _ = Nothing +setPendingScDict :: Ct -> Ct +-- Set the cc_pend_sc flag to True +setPendingScDict ct@(CDictCan { cc_pend_sc = False }) + = ct { cc_pend_sc = True } +setPendingScDict ct = ct + superClassesMightHelp :: Ct -> Bool -- ^ True if taking superclasses of givens, or of wanteds (to perhaps -- expose more equalities or functional dependencies) might help to diff --git a/testsuite/tests/indexed-types/should_compile/T13662.hs b/testsuite/tests/indexed-types/should_compile/T13662.hs new file mode 100644 index 0000000..5898f25 --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T13662.hs @@ -0,0 +1,25 @@ +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE MultiParamTypeClasses #-} +module T13662 (run) where + +newtype Value a = Value a + +type family Repr (f :: * -> *) a :: * +type instance Repr f Int = f Int + +class (Repr Value i ~ Value ir) => Native i ir where + +instance Native Int Int where + + +fromInt :: (Native i ir) => i -> a +fromInt = undefined + +apply :: (Int -> a -> a) -> a -> a +apply weight = id + +run :: Float -> Float +run = + let weight = \clip v -> fromInt clip * v + in apply weight + diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index 529f7de..00d40ce 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -263,3 +263,4 @@ test('T12538', normal, compile_fail, ['']) test('T13244', normal, compile, ['']) test('T13398a', normal, compile, ['']) test('T13398b', normal, compile, ['']) +test('T13662', normal, compile, ['']) From git at git.haskell.org Tue May 16 01:12:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 01:12:05 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: compiler: Do not look up fail in RnExpr if bind pattern is irrefutible. (56a4863) Message-ID: <20170516011205.7D0AF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/56a4863b25687319a07db596bd47d724456317a5/ghc >--------------------------------------------------------------- commit 56a4863b25687319a07db596bd47d724456317a5 Author: Aaron Friel Date: Thu May 11 15:41:22 2017 -0400 compiler: Do not look up fail in RnExpr if bind pattern is irrefutible. Adds a check in `rnStmt`, in sub-expr `getFailFunction`, to determine if the pattern of a bind statement is irrefutible. If so, skip looking up the `fail` name. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13649 Differential Revision: https://phabricator.haskell.org/D3553 (cherry picked from commit 2fcb5c5c3f6c5a5936eeb5dc07b476e5737f12ad) >--------------------------------------------------------------- 56a4863b25687319a07db596bd47d724456317a5 compiler/rename/RnExpr.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/compiler/rename/RnExpr.hs b/compiler/rename/RnExpr.hs index 4e9192c..fe3d308 100644 --- a/compiler/rename/RnExpr.hs +++ b/compiler/rename/RnExpr.hs @@ -824,6 +824,10 @@ rnStmt ctxt rnBody (L loc (BindStmt pat body _ _ _)) thing_inside ; xMonadFailEnabled <- fmap (xopt LangExt.MonadFailDesugaring) getDynFlags ; let getFailFunction + -- If the pattern is irrefutible (e.g.: wildcard, tuple, + -- ~pat, etc.) we should not need to fail. + | isIrrefutableHsPat pat + = return (noSyntaxExpr, emptyFVs) -- For non-monadic contexts (e.g. guard patterns, list -- comprehensions, etc.) we should not need to fail. -- See Note [Failing pattern matches in Stmts] From git at git.haskell.org Tue May 16 01:12:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 01:12:09 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix incorrect ambiguity error on identically-named data constructors (343cb32) Message-ID: <20170516011209.129C43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/343cb32d0983f576d344a2d04a35c3fd6eecf2c5/ghc >--------------------------------------------------------------- commit 343cb32d0983f576d344a2d04a35c3fd6eecf2c5 Author: Soham Chowdhury Date: Thu May 11 15:40:18 2017 -0400 Fix incorrect ambiguity error on identically-named data constructors Given multiple in-scope constructors with the same name, say `A`, and a function of type `A -> Int`, say, the compiler reports both a "type `A` is not in scope" and (incorrectly) an ambiguity error. The latter shouldn't be there if `DataKinds` isn't enabled. This issue was recommended to me by @mpickering as a suitable first task, and the fix was also outlined in the original Trac ticket. It involved a simple reordering of the steps taken in `lookup_demoted` in `RnEnv.hs`. The fix is to make the `DataKinds` check happen earlier, ensuring that the ambiguity check doesn't happen at all if we know the constructors couldn't have been promoted. Signed-off-by: Soham Chowdhury Reviewers: mpickering, austin, bgamari Reviewed By: mpickering, bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13568 Differential Revision: https://phabricator.haskell.org/D3547 (cherry picked from commit 1381c142cd8d030f9997cdc206dcad006c028bbb) >--------------------------------------------------------------- 343cb32d0983f576d344a2d04a35c3fd6eecf2c5 compiler/rename/RnEnv.hs | 21 +++++++++++---------- testsuite/tests/module/mod122.stderr | 4 +++- testsuite/tests/module/mod123.stderr | 4 +++- testsuite/tests/module/mod124.stderr | 1 + testsuite/tests/module/mod127.stderr | 1 + testsuite/tests/module/mod29.stderr | 1 + testsuite/tests/module/mod50.stderr | 4 +++- .../tests/parser/should_fail/readFail001.stderr | 1 + .../tests/rename/prog003/rename.prog003.stderr | 4 +++- testsuite/tests/rename/should_fail/T13568.hs | 8 ++++++++ testsuite/tests/rename/should_fail/T13568.stderr | 4 ++++ testsuite/tests/rename/should_fail/T13568a.hs | 3 +++ testsuite/tests/rename/should_fail/T1595a.stderr | 4 +++- testsuite/tests/rename/should_fail/T5745.stderr | 4 +++- testsuite/tests/rename/should_fail/all.T | 1 + testsuite/tests/typecheck/should_fail/T1595.stderr | 6 ++++-- .../tests/typecheck/should_fail/tcfail048.stderr | 4 +++- .../tests/typecheck/should_fail/tcfail053.stderr | 4 +++- 18 files changed, 59 insertions(+), 20 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 343cb32d0983f576d344a2d04a35c3fd6eecf2c5 From git at git.haskell.org Tue May 16 01:12:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 01:12:12 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix collect_lpat's treatment of HsSplicedPats (72015ab) Message-ID: <20170516011212.62B1E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/72015aba0af37e0547150299049591e2a0ced270/ghc >--------------------------------------------------------------- commit 72015aba0af37e0547150299049591e2a0ced270 Author: Ryan Scott Date: Thu May 11 15:46:02 2017 -0400 Fix collect_lpat's treatment of HsSplicedPats `collect_lpat` was missing a case for `HsSplicedPat`, which caused incorrect renaming of TH-spliced pattern variables. Fixes #13473. Test Plan: make test TEST=T13473 Reviewers: facundominguez, austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13473 Differential Revision: https://phabricator.haskell.org/D3572 (cherry picked from commit eaf9cc4240019c2e91922ef38ae7236b59d59bdd) >--------------------------------------------------------------- 72015aba0af37e0547150299049591e2a0ced270 compiler/hsSyn/HsUtils.hs | 3 +++ testsuite/tests/th/T13473.hs | 13 +++++++++++++ .../{deSugar/should_run/T13285.stdout => th/T13473.stdout} | 0 testsuite/tests/th/T13473a.hs | 10 ++++++++++ testsuite/tests/th/all.T | 2 ++ 5 files changed, 28 insertions(+) diff --git a/compiler/hsSyn/HsUtils.hs b/compiler/hsSyn/HsUtils.hs index c7d43b0..d19e45b 100644 --- a/compiler/hsSyn/HsUtils.hs +++ b/compiler/hsSyn/HsUtils.hs @@ -958,6 +958,9 @@ collect_lpat (L _ pat) bndrs go (SigPatIn pat _) = collect_lpat pat bndrs go (SigPatOut pat _) = collect_lpat pat bndrs + + go (SplicePat (HsSpliced _ (HsSplicedPat pat))) + = go pat go (SplicePat _) = bndrs go (CoPat _ pat _) = go pat diff --git a/testsuite/tests/th/T13473.hs b/testsuite/tests/th/T13473.hs new file mode 100644 index 0000000..d977626 --- /dev/null +++ b/testsuite/tests/th/T13473.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE QuasiQuotes #-} +{-# LANGUAGE TemplateHaskell #-} +module Main where + +import Language.Haskell.TH +import T13473a + +[quoter|y|] = 1 + +main :: IO () +main = do + let $(varP $ mkName "x") = 1 in print x + print y diff --git a/testsuite/tests/deSugar/should_run/T13285.stdout b/testsuite/tests/th/T13473.stdout similarity index 100% copy from testsuite/tests/deSugar/should_run/T13285.stdout copy to testsuite/tests/th/T13473.stdout diff --git a/testsuite/tests/th/T13473a.hs b/testsuite/tests/th/T13473a.hs new file mode 100644 index 0000000..fcd6ebb --- /dev/null +++ b/testsuite/tests/th/T13473a.hs @@ -0,0 +1,10 @@ +module T13473a where + +import Language.Haskell.TH +import Language.Haskell.TH.Quote + +quoter :: QuasiQuoter +quoter = QuasiQuoter { quotePat = varP . mkName + , quoteExp = undefined + , quoteDec = undefined + , quoteType = undefined } diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 4037a8f..06fbdcd 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -381,5 +381,7 @@ test('T13123', normal, compile, ['-v0']) test('T13098', normal, compile, ['-v0']) test('T11046', normal, multimod_compile, ['T11046','-v0']) test('T13366', normal, compile_and_run, ['-lstdc++ -v0']) +test('T13473', normal, multimod_compile_and_run, + ['T13473.hs', '-v0 ' + config.ghc_th_way_flags]) test('T13618', normal, compile_and_run, ['-v0']) test('T13642', normal, compile_fail, ['-v0']) From git at git.haskell.org Tue May 16 01:12:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 01:12:15 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: users-guide: Document requirement of at least one -dep-suffix (e84b18d) Message-ID: <20170516011215.1B19C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/e84b18dfa98c3d2fc9c9288203113a2fbca406ba/ghc >--------------------------------------------------------------- commit e84b18dfa98c3d2fc9c9288203113a2fbca406ba Author: Ben Gamari Date: Thu May 11 16:49:54 2017 -0400 users-guide: Document requirement of at least one -dep-suffix This requirement was introduced around 7.8 but was never documented. Resolves #9287. (cherry picked from commit b9d1dae0c0ee0bd3b7e9be3c83ce932d837944f1) >--------------------------------------------------------------- e84b18dfa98c3d2fc9c9288203113a2fbca406ba docs/users_guide/separate_compilation.rst | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/docs/users_guide/separate_compilation.rst b/docs/users_guide/separate_compilation.rst index a140d46..0c981d5 100644 --- a/docs/users_guide/separate_compilation.rst +++ b/docs/users_guide/separate_compilation.rst @@ -1188,13 +1188,14 @@ generation are: .. ghc-flag:: -dep-suffix - Make extra dependencies that declare that files with suffix - ``._`` depend on interface files with suffix - ``._hi``, or (for ``{-# SOURCE #-}`` imports) on ``.hi-boot``. + Make dependencies that declare that files with suffix + ``.`` depend on interface files with suffix + ``.hi``, or (for ``{-# SOURCE #-}`` imports) on ``.hi-boot``. Multiple ``-dep-suffix`` flags are permitted. For example, - ``-dep-suffix a -dep-suffix b`` will make dependencies for ``.hs`` + ``-dep-suffix a_ -dep-suffix b_`` will make dependencies for ``.hs`` on ``.hi``, ``.a_hs`` on ``.a_hi``, and ``.b_hs`` on ``.b_hi``. - (Useful in conjunction with NoFib "ways".) + Note that you must provide at least one suffix; if you do not want a suffix + then pass ``-dep-suffix ''``. .. ghc-flag:: --exclude-module= From git at git.haskell.org Tue May 16 01:12:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 01:12:20 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: OptCoercion: Ensure that TyConApps match in arity (ca76ae0) Message-ID: <20170516011220.813E63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/ca76ae071d9ffb4f36fc4b59ef9fa3bf3dfe2b8a/ghc >--------------------------------------------------------------- commit ca76ae071d9ffb4f36fc4b59ef9fa3bf3dfe2b8a Author: Ben Gamari Date: Mon May 8 17:40:50 2017 -0400 OptCoercion: Ensure that TyConApps match in arity Previously OptCoercion would potentially change the type of UnivCo coercions of the shape, ``` co :: TyCon arg1 ... argN ~ TyCon arg1' ... argN' ``` where the arities of the left and right applications differ. In this case we would try to zip the two argument lists, meaning that one would get truncated. One would think this could never happen since it implies we are applying the same TyCon to two different numbers of arguments. However, it does arise in the case of applications of the `Any` tycon, which arises from the typechecker (in `Data.Typeable.Internal`) where we end up with an `UnsafeCo`, ``` co :: Any (Any -> Any) Any ~ Any (Any -> Any) ``` Test Plan: Validate Reviewers: simonpj, austin, goldfire Reviewed By: simonpj Subscribers: rwbarton, thomie GHC Trac Issues: #13658 Differential Revision: https://phabricator.haskell.org/D3545 (cherry picked from commit 87ff5d4f0f812bad118600df0156f980b91191c5) >--------------------------------------------------------------- ca76ae071d9ffb4f36fc4b59ef9fa3bf3dfe2b8a compiler/types/OptCoercion.hs | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/compiler/types/OptCoercion.hs b/compiler/types/OptCoercion.hs index 7f96754..2e6c00e 100644 --- a/compiler/types/OptCoercion.hs +++ b/compiler/types/OptCoercion.hs @@ -364,6 +364,20 @@ opt_phantom env sym co where Pair ty1 ty2 = coercionKind co +{- Note [Differing kinds] + ~~~~~~~~~~~~~~~~~~~~~~ +The two types may not have the same kind (although that would be very unusual). +But even if they have the same kind, and the same type constructor, the number +of arguments in a `CoTyConApp` can differ. Consider + + Any :: forall k. k + + Any * Int :: * + Any (*->*) Maybe Int :: * + +Hence the need to compare argument lengths; see Trac #13658 + -} + opt_univ :: LiftingContext -> SymFlag -> UnivCoProvenance -> Role -> Type -> Type -> Coercion opt_univ env sym (PhantomProv h) _r ty1 ty2 @@ -378,6 +392,7 @@ opt_univ env sym prov role oty1 oty2 | Just (tc1, tys1) <- splitTyConApp_maybe oty1 , Just (tc2, tys2) <- splitTyConApp_maybe oty2 , tc1 == tc2 + , equalLength tys1 tys2 -- see Note [Differing kinds] -- NB: prov must not be the two interesting ones (ProofIrrel & Phantom); -- Phantom is already taken care of, and ProofIrrel doesn't relate tyconapps = let roles = tyConRolesX role tc1 From git at git.haskell.org Tue May 16 01:12:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 01:12:17 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix crash in isModuleInterpreted for HsBoot (fixes #13591) (f3ce368) Message-ID: <20170516011217.C5D2F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/f3ce36846bd3da3d957810f05d387d7699cd23e1/ghc >--------------------------------------------------------------- commit f3ce36846bd3da3d957810f05d387d7699cd23e1 Author: Lennart Spitzner Date: Wed May 10 16:47:19 2017 +0200 Fix crash in isModuleInterpreted for HsBoot (fixes #13591) Rename isModuleInterpreted to moduleIsBootOrNotObjectLinkable because a) there already is a moduleIsInterpreted function in the same module b) I have no idea if the (new) semantic of the bool returned matches some understanding of "is interpreted". (cherry picked from commit 1edee7a8b5ca24156cb6e21bde6d611a0ba63882) >--------------------------------------------------------------- f3ce36846bd3da3d957810f05d387d7699cd23e1 compiler/main/GHC.hs | 2 +- compiler/main/InteractiveEval.hs | 14 +++++++------- ghc/GHCi/UI.hs | 2 +- 3 files changed, 9 insertions(+), 9 deletions(-) diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index 53e135c..0f7acbf 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -112,7 +112,7 @@ module GHC ( moduleIsInterpreted, getInfo, showModule, - isModuleInterpreted, + moduleIsBootOrNotObjectLinkable, -- ** Inspecting types and kinds exprType, TcRnExprMode(..), diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs index 1fa2698..0d83b48 100644 --- a/compiler/main/InteractiveEval.hs +++ b/compiler/main/InteractiveEval.hs @@ -31,7 +31,7 @@ module InteractiveEval ( typeKind, parseName, showModule, - isModuleInterpreted, + moduleIsBootOrNotObjectLinkable, parseExpr, compileParsedExpr, compileExpr, dynCompileExpr, compileExprRemote, compileParsedExprRemote, @@ -901,17 +901,17 @@ dynCompileExpr expr = do showModule :: GhcMonad m => ModSummary -> m String showModule mod_summary = withSession $ \hsc_env -> do - interpreted <- isModuleInterpreted mod_summary + interpreted <- moduleIsBootOrNotObjectLinkable mod_summary let dflags = hsc_dflags hsc_env return (showModMsg dflags (hscTarget dflags) interpreted mod_summary) -isModuleInterpreted :: GhcMonad m => ModSummary -> m Bool -isModuleInterpreted mod_summary = withSession $ \hsc_env -> +moduleIsBootOrNotObjectLinkable :: GhcMonad m => ModSummary -> m Bool +moduleIsBootOrNotObjectLinkable mod_summary = withSession $ \hsc_env -> case lookupHpt (hsc_HPT hsc_env) (ms_mod_name mod_summary) of Nothing -> panic "missing linkable" - Just mod_info -> return (not obj_linkable) - where - obj_linkable = isObjectLinkable (expectJust "showModule" (hm_linkable mod_info)) + Just mod_info -> return $ case hm_linkable mod_info of + Nothing -> True + Just linkable -> not (isObjectLinkable linkable) ---------------------------------------------------------------------------- -- RTTI primitives diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs index 44f0935..a509f28 100644 --- a/ghc/GHCi/UI.hs +++ b/ghc/GHCi/UI.hs @@ -1801,7 +1801,7 @@ modulesLoadedMsg ok mods = do dflags <- getDynFlags unqual <- GHC.getPrintUnqual let mod_name mod = do - is_interpreted <- GHC.isModuleInterpreted mod + is_interpreted <- GHC.moduleIsBootOrNotObjectLinkable mod return $ if is_interpreted then ppr (GHC.ms_mod mod) else ppr (GHC.ms_mod mod) From git at git.haskell.org Tue May 16 01:12:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 01:12:23 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: testsuite: Add testcase for T13658 (3906a0c) Message-ID: <20170516011223.93E503A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/3906a0c0c95f4c9a36479c38776de74b36013a99/ghc >--------------------------------------------------------------- commit 3906a0c0c95f4c9a36479c38776de74b36013a99 Author: Ben Gamari Date: Mon May 15 20:15:11 2017 -0400 testsuite: Add testcase for T13658 (cherry picked from commit efd113f72f07908e57c62cbce71f8d4a1e1d2819) >--------------------------------------------------------------- 3906a0c0c95f4c9a36479c38776de74b36013a99 testsuite/tests/simplCore/should_compile/T13658.hs | 39 ++++++++++++++++++++++ testsuite/tests/simplCore/should_compile/all.T | 1 + 2 files changed, 40 insertions(+) diff --git a/testsuite/tests/simplCore/should_compile/T13658.hs b/testsuite/tests/simplCore/should_compile/T13658.hs new file mode 100644 index 0000000..0890e89 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T13658.hs @@ -0,0 +1,39 @@ +{-# LANGUAGE TypeInType #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE BangPatterns #-} + +{- # OPTIONS_GHC -Werror #-} +{-# OPTIONS_GHC -g -O2 #-} + +module Bug (bug) where + +-- import GHC.Base (seq) +import Unsafe.Coerce (unsafeCoerce) + +undefined :: a +undefined = undefined + +data TypeRep (a :: k) where + TrTyCon :: TypeRep (a :: k) + TrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1). + TypeRep (a b) + +data SomeTypeRep where + SomeTypeRep :: forall k (a :: k). + TypeRep a + -> SomeTypeRep + +mkTrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1). + TypeRep (a :: k1 -> k2) + -> TypeRep (a b) +mkTrApp TrTyCon = undefined +mkTrApp TrApp = undefined + +bug :: SomeTypeRep +-- bug = f x -- this works +bug = f (f x) + where x = SomeTypeRep TrTyCon + f :: SomeTypeRep -> SomeTypeRep + f (SomeTypeRep acc) = SomeTypeRep (mkTrApp (unsafeCoerce acc)) diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index 7a079c7..3e25b87 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -259,3 +259,4 @@ test('T13468', normal, run_command, ['$MAKE -s --no-print-directory T13468']) +test('T13658', normal, compile, ['-dcore-lint']) From git at git.haskell.org Tue May 16 14:47:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 14:47:09 +0000 (UTC) Subject: [commit: ghc] master: Kill off unused IfaceType.eqIfaceType (2c21d74) Message-ID: <20170516144709.64CD13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2c21d74cb1778eb390ee8d71465136fcd8289f4a/ghc >--------------------------------------------------------------- commit 2c21d74cb1778eb390ee8d71465136fcd8289f4a Author: Simon Peyton Jones Date: Tue May 16 11:56:23 2017 +0100 Kill off unused IfaceType.eqIfaceType Edward implemented these functions, but they aren't used any more. Trac #13679 >--------------------------------------------------------------- 2c21d74cb1778eb390ee8d71465136fcd8289f4a compiler/iface/IfaceSyn.hs | 7 +-- compiler/iface/IfaceType.hs | 134 ++++++-------------------------------------- 2 files changed, 21 insertions(+), 120 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 2c21d74cb1778eb390ee8d71465136fcd8289f4a From git at git.haskell.org Tue May 16 14:47:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 14:47:12 +0000 (UTC) Subject: [commit: ghc] master: Tiny refactor (fea9a75) Message-ID: <20170516144712.3218B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fea9a7570dd6fd8d2b690bc378af01db3662dbdb/ghc >--------------------------------------------------------------- commit fea9a7570dd6fd8d2b690bc378af01db3662dbdb Author: Simon Peyton Jones Date: Tue May 16 15:42:34 2017 +0100 Tiny refactor >--------------------------------------------------------------- fea9a7570dd6fd8d2b690bc378af01db3662dbdb compiler/typecheck/TcInteract.hs | 14 +++++++++----- 1 file changed, 9 insertions(+), 5 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 5792dfb..4368fcb 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1739,17 +1739,21 @@ improve_top_fun_eqs fam_envs fam_tc args rhs_ty -- see Note [Type inference for type families with injectivity] | isOpenTypeFamilyTyCon fam_tc , Injective injective_args <- familyTyConInjectivityInfo fam_tc + , let fam_insts = lookupFamInstEnvByTyCon fam_envs fam_tc = -- it is possible to have several compatible equations in an open type -- family but we only want to derive equalities from one such equation. - concatMapM (injImproveEqns injective_args) (take 1 $ - buildImprovementData (lookupFamInstEnvByTyCon fam_envs fam_tc) - fi_tvs fi_tys fi_rhs (const Nothing)) + do { let improvs = buildImprovementData fam_insts + fi_tvs fi_tys fi_rhs (const Nothing) + + ; traceTcS "improve_top_fun_eqs2" (ppr improvs) + ; concatMapM (injImproveEqns injective_args) $ + take 1 improvs } | Just ax <- isClosedSynFamilyTyConWithAxiom_maybe fam_tc , Injective injective_args <- familyTyConInjectivityInfo fam_tc = concatMapM (injImproveEqns injective_args) $ - buildImprovementData (fromBranches (co_ax_branches ax)) - cab_tvs cab_lhs cab_rhs Just + buildImprovementData (fromBranches (co_ax_branches ax)) + cab_tvs cab_lhs cab_rhs Just | otherwise = return [] From git at git.haskell.org Tue May 16 14:47:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 14:47:15 +0000 (UTC) Subject: [commit: ghc] master: Fix the pure unifier (cec7d58) Message-ID: <20170516144715.A7E6D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cec7d580c2c033c3aaeba093752328d8f3635cd0/ghc >--------------------------------------------------------------- commit cec7d580c2c033c3aaeba093752328d8f3635cd0 Author: Simon Peyton Jones Date: Tue May 16 15:43:55 2017 +0100 Fix the pure unifier This patch fixes Trac #13705, by fixing a long-standing outright bug in the pure unifier. I'm surprised this hasn't caused more trouble before now! >--------------------------------------------------------------- cec7d580c2c033c3aaeba093752328d8f3635cd0 compiler/types/Unify.hs | 380 ++++++++++----------- .../tests/indexed-types/should_compile/T13705.hs | 15 + testsuite/tests/indexed-types/should_compile/all.T | 1 + 3 files changed, 200 insertions(+), 196 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 cec7d580c2c033c3aaeba093752328d8f3635cd0 From git at git.haskell.org Tue May 16 20:21:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 20:21:05 +0000 (UTC) Subject: [commit: ghc] wip/cross-spec-constr: Working to the first degree (fa4ffa0) Message-ID: <20170516202105.4157F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cross-spec-constr Link : http://ghc.haskell.org/trac/ghc/changeset/fa4ffa0adc8b5fd1a4891d3a490213b8fcb3aaa9/ghc >--------------------------------------------------------------- commit fa4ffa0adc8b5fd1a4891d3a490213b8fcb3aaa9 Author: Matthew Pickering Date: Wed May 10 14:26:43 2017 +0100 Working to the first degree >--------------------------------------------------------------- fa4ffa0adc8b5fd1a4891d3a490213b8fcb3aaa9 compiler/specialise/SpecConstr.hs | 257 +++++++++++++++++++++++++++++++------- compiler/specialise/Specialise.hs | 1 + 2 files changed, 216 insertions(+), 42 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 fa4ffa0adc8b5fd1a4891d3a490213b8fcb3aaa9 From git at git.haskell.org Tue May 16 20:21:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 20:21:10 +0000 (UTC) Subject: [commit: ghc] wip/cross-spec-constr: more aggressive (ca45aa6) Message-ID: <20170516202110.C57853A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cross-spec-constr Link : http://ghc.haskell.org/trac/ghc/changeset/ca45aa68706e6bb2e9ad785749c31da8027ad495/ghc >--------------------------------------------------------------- commit ca45aa68706e6bb2e9ad785749c31da8027ad495 Author: Matthew Pickering Date: Sun May 14 15:33:21 2017 +0100 more aggressive >--------------------------------------------------------------- ca45aa68706e6bb2e9ad785749c31da8027ad495 compiler/specialise/SpecConstr.hs | 9 ++------- 1 file changed, 2 insertions(+), 7 deletions(-) diff --git a/compiler/specialise/SpecConstr.hs b/compiler/specialise/SpecConstr.hs index 2467611..97a0126 100644 --- a/compiler/specialise/SpecConstr.hs +++ b/compiler/specialise/SpecConstr.hs @@ -828,13 +828,8 @@ wantSpecImport dflags unf BootUnfolding -> False OtherCon {} -> False DFunUnfolding {} -> True - CoreUnfolding { uf_src = src, uf_guidance = _guidance } - | gopt Opt_SpecialiseAggressively dflags -> True - | isStableSource src -> True - -- Specialise even INLINE things; it hasn't inlined yet, - -- so perhaps it never will. Moreover it may have calls - -- inside it that we want to specialise - | otherwise -> False -- Stable, not INLINE, hence INLINABLE + CoreUnfolding { uf_src = src, uf_guidance = _guidance } -> True + {- ************************************************************************ * * From git at git.haskell.org Tue May 16 20:21:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 20:21:08 +0000 (UTC) Subject: [commit: ghc] wip/cross-spec-constr: WIP: Make SpecConstr work across modules (5a247be) Message-ID: <20170516202108.1074E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cross-spec-constr Link : http://ghc.haskell.org/trac/ghc/changeset/5a247bea70ce1a2c971928c4300970d3a7f269d4/ghc >--------------------------------------------------------------- commit 5a247bea70ce1a2c971928c4300970d3a7f269d4 Author: Matthew Pickering Date: Wed May 10 15:44:36 2017 +0100 WIP: Make SpecConstr work across modules Summary: This enables the SpecConst transformation to work across modules. I mostly copied and modified code from the normal specialiser and it seems to work. Here to validate and get feedback. TODO: []: Work out what SpecConstr actually does []: Add a test []: Clean up the mostly copied implementation Reviewers: simonpj, austin, bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #10346 Differential Revision: https://phabricator.haskell.org/D3566 >--------------------------------------------------------------- 5a247bea70ce1a2c971928c4300970d3a7f269d4 compiler/specialise/SpecConstr.hs | 112 +++++++++++++++++++------------------- compiler/specialise/Specialise.hs | 2 +- 2 files changed, 58 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 5a247bea70ce1a2c971928c4300970d3a7f269d4 From git at git.haskell.org Tue May 16 20:21:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 May 2017 20:21:14 +0000 (UTC) Subject: [commit: ghc] wip/cross-spec-constr's head updated: more aggressive (ca45aa6) Message-ID: <20170516202114.09E5D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/cross-spec-constr' now includes: 037c249 Fix a couple of user-manual typos 0ae7251 Yet more work on TcSimplify.simplifyInfer fbb27d7 Remove dead quantifyTyVars 87078ef Comments only in Type.isPredTy 1c6ce33 Doc typo 13131ce Fix typo in TcErrors.hs 8a54a4f linters/cpp: Catch #ifndef 6c05b27 linker/mach-o: Catch the case where there is no symCmd 295f97f rts/RtsUtils.c: drop stale comments 5fd75d7 UNREG: remove dead code around -split-objs 29ef714 UNREG: fix spelling of '-split-objs' in warning a92ff5d hs_add_root() RTS API removal 1ca188c configure.ac: print resolved 'ar' and 'ranlib' tools 79848f1 aclocal.m4: respect user's --with-ar= choice ab2dcb1 base: Track timer PSQ timeouts as Word64 instead of Double 3d3975f Fix space leak in sortBy 1cc82d3 utils: Lazily decode UTF8 strings 5a21003 [iserv] drop cryptonite dependency. b894f02 Remove redundant flag (-O) registration (fixes #13392) f58176f Fix "Glasgow Haskell Compiler Users Guide" c87584f Use intersect and minus instead of filter 065be6e Caret diag.: Avoid decoding whole module if only specific line is needed 765a2e7 Update xhtml submodule to potential 3000.2.2 release commit 60699e1 Fix LaTeX in core-spec ebb780f Add failing test case for #13588 fc7601c Revert "linker/mach-o: Catch the case where there is no symCmd" 21c35bd Simplify StgCases when all alts refer to the case binder a18f58d testsuite: disable 'optllvm' for unregisterised compiler 526d2eb pprDebugCLabel: drop duplicate trailing ')' 24cf688 utils/debugNCG: remove old tool a1ffd70 Sync up haskeline submodule to 0.7.4.0 release tag e134af0 base: Fix offset initialization of Windows hLock implementation 3672cf6 testsuite: Bump timeout multiplier for T11195 e5732d2 base: Fix hWaitForInput with timeout on POSIX cfff183 Fix build on DragonflyBSD 69d5ad0 catch the case where there is no symCmd ed5fd53 linters/check-cpp: Demote #if lints to warnings f0751d9 Bump haskeline and terminfo submodules 32a5ba9 Build system: fix bindist for cross-build GHC 58a59d0 Sync up terminfo submodule to 0.4.1.0 release tag 9dd20a3 Edit eventlog-formats.rst to match implementation 363f7fd testsuite: Update performance metrics 3d7c489 base: update comment to match the change from e134af01 c35d63b Bump deepseeq submodule bf67dc7 Bump filepath submodule 5eebb11 Bump time submodule 6cffee6 Haddock submodule update. 8e93799 skip T13525 when running on Windows. f446f6a First update mingw-w64 packages for 8.4 58a6569 configure.ac: print paths to dllwrap and windres fe37e2c aclocal.m4: treat '*-w64-mingw32' targets as windows 745032d rts: tweak cross-compilation to mingw32 0d975a6 Minor reordering of `#include`s fixing compilation on AIX 2fa6873 Fix compilation for !HAVE_FLOCK 8908ba3 ghc: tweak cross-compilation to mingw32 74e5ec9 ghc.mk: fix 'make install' for cross-mingw32 87fbf39 win32/Ticker: Stop ticker on exit f13eebc cpp: Use #pragma once instead of #ifndef guards 1d66f10 rts: Fix "ASSERT ("s e5e8646 [linker] Adds ElfTypes 9eea43f [linker] Adds elf_compat.h, util.h, elf_util.h 18c3a7e Document the kind generalization behavior observed in #13555 317ceb4 Only build iserv with -threaded if GhcThreaded is set f6eaf01 testsuite: Add test for #13591 907b0f3 testsuite: Add testcase for #13587 3efa5be testsuite: Increase T13056 window size to +/-10% 868bdcc testsuite: Add testcase for #13075 1f4fd37 Export function for use in GHC API f799df5 testsuite: Mark T13075 as broken due to #13075 ab27fdc Add regression test for #13603 d5cb4d2 Disable terminfo, if we don’t build it. b68697e compiler/cmm/PprC.hs: constify labels in .rodata 6f9f5ff testsuite/driver: Fix deletion retry logic on Windows 1c27e5b Add failing test case for T13611 cd10a23 Guard yet another /bin/sh `for in` loop against empty vars 583fa9e core-spec: Simplify the handling of LetRec 914842e Don't setProgramDynFlags on every :load 688272b Don't describe tuple sections as "Python-style" 6610886 Revert "Remove special casing of Windows in generic files" 9373994 configure: Kill off FP_ARG_WITH_* 89a3241 PPC NCG: Implement callish prim ops 71c3cea Add backup url and sync support for Win32 tarball script da792e4 Only pretty-print binders in closed type families with -fprint-explicit-foralls 2446026 Document mkWeak# 47be644 Add instances for Data.Ord.Down 350d268 Update hsc2hs submodule to 0.68.2 579bb76 Update Cabal submodule, with necessary wibbles. 2744c94 Bump process to 1.6 7f6674d Comments and tiny refactoring 6c2d917 A bit more tcTrace 4d5ab1f Comments only 03ec792 Comments only 25754c8 Eta expansion and join points a1b753e Cure exponential behaviour in the simplifier 29d88ee Be a bit more eager to inline in a strict context ba597c1 get-win32-tarballs: Grab perl tarball from haskell.org, not GitHub 69b9b85 Add regression test for #12104 b2c38d6 Make the tyvars in TH-reified data family instances uniform 228d467 Use memcpy in cloneArray 9f9b90f CSE: Fix cut and paste error 9ac2218 nativeGen: Use SSE2 SQRT instruction 1cae73a Move dataConTagZ to DataCon 193664d Re-engineer caseRules to add tagToEnum/dataToTag 6d14c14 Improve code generation for conditionals e5b3492 Enable new warning for fragile/incorrect CPP #if usage 945c45a Prefer #if defined to #ifdef 41d9a79 Remove unused tidyOccNames and update Note 821a9f9 testsuite: Widen acceptance window of T13379 0ff7bc8 Update broken nm message 46923b6 Disable -Wcpp-undef for now 7567b9d Ignore ANN pragmas with no TH and no external interpreter. 18fbb9d testsuite: Add test for #13609 c04bd55 Fix capitalization in message for #13609 667abf1 Make LLVM output robust to -dead_strip on mach-o platforms 068af01 PPC NCG: Lower MO_*_Fabs as PowerPC fabs instruction 5c602d2 Avoid excessive space usage from unfoldings in CoreTidy e250178 [linker] Add ocInit/ocDeinit for ELF f2c35d7 Bump array submodule 3746f62 testsuite: Bump allocations of T3064 c46a600 Improve SpecConstr when there are many opportunities 71037b6 Join-point refactoring ff23978 Fix a small Float-Out bug 9e47dc4 Fix loss-of-SpecConstr bug b1aede6 Typos in manual and comments b460d6c Fix #13233 by checking for lev-poly primops ef0ff34 Shave the hair off mkCastTy. 466803a Use mkCastTy in subst_ty. 09bf135 Fix #13333 by fixing the covar's type in ctEvCoercion 16b0a07 Fix #13233 by checking for lev-poly primops 6df8bef Test #13585 in typecheck/should_compile/T13585 239418c Improve fixIO 783dfa7 Teach optCoecion about FunCo 81af480 Abandon typedefing the {Section,ObjectCode}FormatInfo structs e770197 Deal with exceptions in dsWhenNoErrs 2a33f17 Remove unused import 2a09700 Comments only, about Typeable/TypeRep/KindRep cb850e0 Add test for #13320 8a60550 rts: Fix MachO from D3527 41a00fa Bump nofib submodule a660844 Add an Eq instance for UniqSet db10b79 Pass -ffrontend-opt arguments to frontend plugin in the correct order 0b41bbc user-guide: fix links to compact region 4fcaf8e Fix comment for compact region 03ca391 Add regression test for #11616 74f3153 Fix markdown for new GitHub Flavored Markdown 1829d26 Implement sequential name lookup properly 8a2c247 hpc: Output a legend at the top of output files b3da6a6 CoreTidy: Don't seq unfoldings c8e4d4b TcTypeable: Simplify 02748a5 Typos in comments [ci skip] a483e71 tweak to minimize diff against ocInit_ELF 38a3819 Add regression tests for #12947, #13640 4a6cb5e Add testsuite/timeout/TimeMe to .gitignore ed0c7f8 Add regression test for #13651 baa18de testsuite: add new test for desugar warnings/errors with -fno-code 1840121 base: Fix documentation for forkIOWithUnmask 579749d Bump Cabal submodule to the 2.0.0.0 tag c685a44 [Docs] Prefer cost centre 476307c users-guide: Fix a variety of warnings 87ff5d4 OptCoercion: Ensure that TyConApps match in arity ff7a3c4 Optimize casMutVar# for single-threaded RTS dc3b4af Fix Raspberry Pi 0279b74 Make XNegativeLiterals treat -0.0 as negative 0 c5b28e0 Add a failing test for T13644 b99bae6 Dataflow: use IntSet for mkDepBlocks 3729953 Treat banged bindings as FunBinds 85bfd0c testsuite: Fix attribution of "Don't seq unfoldings" regression d46a510 Use mkSymCo in OptCoercion.wrapSym 549c8b3 Don't warn about variable-free strict pattern bindings 6f26fe7 Add regression test for Trac #13659 cb5ca5f Make CallInfo into a data type with fields 43a3168 Reset cc_pend_sc flag in dropDerivedCt 8e72a2e Revert "CoreTidy: Don't seq unfoldings" 22a03e7 Typos [ci skip] 26f509a Efficient membership for home modules 1893ba1 Fix a performance bug in GhcMake.downsweep 4d9167b testsuite: Update allocations for T4801 on Darwin 63ba812 mailmap: Add Douglas Wilson 8d4bce4 libffi via submodule 5ddb307 Do not hardcode the specific linker to use 83dcaa8 [iserv] fix loadDLL b5ca082 We define the `_HOST_ARCH` to `1`, but never to `0`in 094a752 Fix iossimulator 6ef6e7c Drop custom apple handling 418bcf7 bump config.{guess,sub} 1345c7c Pass LLVMTarget (identical to --target) c0872bf Use NEED_PTHREAD_LIB a67cfc7 Revert "libffi via submodule" 2316ee1 Add regression test for #12850 6f99923 pmCheck: Don't generate PmId OccNames from Uniques 1381c14 Fix incorrect ambiguity error on identically-named data constructors 2fcb5c5 compiler: Do not look up fail in RnExpr if bind pattern is irrefutible. aa8dcb3 rts: Don't build StgCRunAsm.S if unregisterised 6e890e8 Add Outputable instance for Node 1f770a5 Use Proxy rather than undefined in MatchLit 2277172 Parenthesize pretty-printed equalities when necessary eaf9cc4 Fix collect_lpat's treatment of HsSplicedPats 01db135 Allow spliced patterns in pattern synonyms b9d1dae users-guide: Document requirement of at least one -dep-suffix 06d2a50 Update autoconf scripts 3e79fe4 Fix up tests for #13594 3760303 testsuite: Fix location of T13594 test a3873e8 RnEnv refactoring fa4ffa0 Working to the first degree 5a247be WIP: Make SpecConstr work across modules ca45aa6 more aggressive From git at git.haskell.org Wed May 17 02:00:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 May 2017 02:00:13 +0000 (UTC) Subject: [commit: ghc] master: Fix #13703 by correctly using munged names in ghc-pkg. (d9e9a9b) Message-ID: <20170517020013.3A2643A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d9e9a9b3016a05e6153de3803998877f91c6cdf4/ghc >--------------------------------------------------------------- commit d9e9a9b3016a05e6153de3803998877f91c6cdf4 Author: Edward Z. Yang Date: Mon May 15 21:17:45 2017 -0700 Fix #13703 by correctly using munged names in ghc-pkg. Summary: Cabal internal libraries are implemented using a trick, where the 'name' field in ghc-pkg registration file is munged into a new form to keep each internal library looking like a distinct package to ghc-pkg and other tools; e.g. the internal library q from package p is named z-p-z-q. Later, Cabal library got refactored so that we made a closer distinction between these "munged" package names and the true package name of a package. Unfortunately, this is an example of a refactor for clarity in the source code which ends up causing problems downstream, because the point of "munging" the package name was to make it so that ghc-pkg and similar tools transparently used MungedPackageName whereever they previously used PackageName (in preparation for them learning proper syntax for package name + component name). Failing to do this meant that internal libraries from the same package (but with different names) clobber each other. This commit search-replaces most occurrences of PackageName in ghc-pkg and turns them into MungedPackageName. Otherwise there shouldn't be any functional differenes. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: bgamari, austin Subscribers: rwbarton, thomie GHC Trac Issues: #13703 Differential Revision: https://phabricator.haskell.org/D3590 >--------------------------------------------------------------- d9e9a9b3016a05e6153de3803998877f91c6cdf4 testsuite/.gitignore | 1 + testsuite/tests/cabal/Makefile | 8 +++++ testsuite/tests/cabal/T13703.stdout | 4 +++ testsuite/tests/cabal/all.T | 2 ++ testsuite/tests/cabal/test13703a.pkg | 20 +++++++++++ testsuite/tests/cabal/test13703b.pkg | 20 +++++++++++ utils/ghc-pkg/Main.hs | 66 +++++++++++++++++++----------------- 7 files changed, 89 insertions(+), 32 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 d9e9a9b3016a05e6153de3803998877f91c6cdf4 From git at git.haskell.org Wed May 17 12:48:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 May 2017 12:48:12 +0000 (UTC) Subject: [commit: ghc] master: Handle type-lets better (d6461f9) Message-ID: <20170517124812.45F2F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d6461f9684f6f758320a5e5afbf0634fcc2996a5/ghc >--------------------------------------------------------------- commit d6461f9684f6f758320a5e5afbf0634fcc2996a5 Author: Simon Peyton Jones Date: Wed May 17 09:44:46 2017 +0100 Handle type-lets better Core allows non-recursive type-lets, thus let a = TYPE ty in ... They are substituted away very quickly, but it's convenient for some passes to produce them (rather than to have to substitute immediately). Trac #13708 tried the effect of not running the simplifer at all (a rather bizarre thing to do, but still). That showed that some passes crashed because they always treated a let-bounder binder as an Id. This patch adds some easy fixes. >--------------------------------------------------------------- d6461f9684f6f758320a5e5afbf0634fcc2996a5 compiler/basicTypes/Id.hs | 6 +++-- compiler/basicTypes/Var.hs | 4 ++-- compiler/coreSyn/CoreFVs.hs | 27 ++++++++-------------- compiler/simplCore/CSE.hs | 14 +++++++---- compiler/simplCore/FloatIn.hs | 4 ++-- testsuite/tests/simplCore/should_compile/T13708.hs | 11 +++++++++ testsuite/tests/simplCore/should_compile/all.T | 1 + 7 files changed, 39 insertions(+), 28 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 d6461f9684f6f758320a5e5afbf0634fcc2996a5 From git at git.haskell.org Thu May 18 00:23:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 00:23:11 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add THREADS parameter (d5f713c) Message-ID: <20170518002311.CAB1D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d5f713ca3767176a118d922494515db8d4b704eb/ghc >--------------------------------------------------------------- commit d5f713ca3767176a118d922494515db8d4b704eb Author: Ben Gamari Date: Sat May 13 11:59:37 2017 -0400 Add THREADS parameter >--------------------------------------------------------------- d5f713ca3767176a118d922494515db8d4b704eb Jenkinsfile | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index f643e51..b661917 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,7 +1,8 @@ pipeline { agent any parameters { - booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), + string(name: 'THREADS', defaultValue: '2', description: 'available parallelism') } stages { From git at git.haskell.org Thu May 18 00:23:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 00:23:14 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring (88a02b2) Message-ID: <20170518002314.84A323A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/88a02b241a354904fb8a9f6a1737e6c8c50ef12a/ghc >--------------------------------------------------------------- commit 88a02b241a354904fb8a9f6a1737e6c8c50ef12a Author: Ben Gamari Date: Wed May 17 20:20:55 2017 -0400 Refactoring >--------------------------------------------------------------- 88a02b241a354904fb8a9f6a1737e6c8c50ef12a Jenkinsfile | 46 ++++++++++++++++++++++++++++++++++++---------- 1 file changed, 36 insertions(+), 10 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index b661917..0142546 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,21 +1,47 @@ +def buildGhc() { + steps { + sh 'git submodule update --init --recursive' + def speed = 'NORMAL' + if (params.nightly) { + speed = 'SLOW' + } + writeFile 'mk/build.mk' + ''' + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + ''' + sh ''' + ./boot + ./configure --enable-tarballs-autodownload + make THREADS=${params.threads} test + ''' + } +} + pipeline { agent any parameters { booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), - string(name: 'THREADS', defaultValue: '2', description: 'available parallelism') + string(name: 'threads', defaultValue: '2', description: 'available parallelism') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?'), } stages { stage('Build') { - steps { - sh 'git submodule update --init --recursive' - sh ''' - ./boot - ./configure --enable-tarballs-autodownload - make -j$THREADS - make THREADS=$THREADS test - ''' - } + buildGhc + } + + stage('Normal testsuite run') { + when { environment name: 'nightly', value: false } + sh 'make THREADS=${params.threads} test' + } + + stage('Slow testsuite run') { + when { environment name: 'nightly', value: true } + sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' + sh 'make THREADS=${params.threads} slowtest' } } } From git at git.haskell.org Thu May 18 00:24:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 00:24:22 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring (65c8cc0) Message-ID: <20170518002422.4EF243A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/65c8cc0c87ef22116c2086128c17b5ae42d628e4/ghc >--------------------------------------------------------------- commit 65c8cc0c87ef22116c2086128c17b5ae42d628e4 Author: Ben Gamari Date: Wed May 17 20:20:55 2017 -0400 Refactoring >--------------------------------------------------------------- 65c8cc0c87ef22116c2086128c17b5ae42d628e4 Jenkinsfile | 48 +++++++++++++++++++++++++++++++++++++----------- 1 file changed, 37 insertions(+), 11 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index b661917..aa49965 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,21 +1,47 @@ +def buildGhc() { + steps { + sh 'git submodule update --init --recursive' + def speed = 'NORMAL' + if (params.nightly) { + speed = 'SLOW' + } + writeFile 'mk/build.mk' + ''' + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + ''' + sh ''' + ./boot + ./configure --enable-tarballs-autodownload + make THREADS=${params.threads} test + ''' + } +} + pipeline { agent any parameters { - booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), - string(name: 'THREADS', defaultValue: '2', description: 'available parallelism') + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') + string(name: 'threads', defaultValue: '2', description: 'available parallelism') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') } stages { stage('Build') { - steps { - sh 'git submodule update --init --recursive' - sh ''' - ./boot - ./configure --enable-tarballs-autodownload - make -j$THREADS - make THREADS=$THREADS test - ''' - } + buildGhc + } + + stage('Normal testsuite run') { + when { environment name: 'nightly', value: false } + sh 'make THREADS=${params.threads} test' + } + + stage('Slow testsuite run') { + when { environment name: 'nightly', value: true } + sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' + sh 'make THREADS=${params.threads} slowtest' } } } From git at git.haskell.org Thu May 18 00:26:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 00:26:10 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring (e31808d) Message-ID: <20170518002610.650743A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/e31808d4657f7f26fea2a202ec9eee45b19905f8/ghc >--------------------------------------------------------------- commit e31808d4657f7f26fea2a202ec9eee45b19905f8 Author: Ben Gamari Date: Wed May 17 20:20:55 2017 -0400 Refactoring >--------------------------------------------------------------- e31808d4657f7f26fea2a202ec9eee45b19905f8 Jenkinsfile | 48 +++++++++++++++++++++++++++++++++++++++--------- 1 file changed, 39 insertions(+), 9 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index b661917..337b560 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,20 +1,50 @@ +def buildGhc() { + steps { + sh 'git submodule update --init --recursive' + def speed = 'NORMAL' + if (params.nightly) { + speed = 'SLOW' + } + writeFile 'mk/build.mk' + ''' + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + ''' + sh ''' + ./boot + ./configure --enable-tarballs-autodownload + make THREADS=${params.threads} test + ''' + } +} + pipeline { agent any parameters { - booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), - string(name: 'THREADS', defaultValue: '2', description: 'available parallelism') + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') + string(name: 'threads', defaultValue: '2', description: 'available parallelism') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') } stages { stage('Build') { + buildGhc + } + + stage('Normal testsuite run') { + when { environment name: 'nightly', value: false } + steps { + sh 'make THREADS=${params.threads} test' + } + } + + stage('Slow testsuite run') { + when { environment name: 'nightly', value: true } steps { - sh 'git submodule update --init --recursive' - sh ''' - ./boot - ./configure --enable-tarballs-autodownload - make -j$THREADS - make THREADS=$THREADS test - ''' + sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' + sh 'make THREADS=${params.threads} slowtest' } } } From git at git.haskell.org Thu May 18 00:32:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 00:32:10 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring (2aff917) Message-ID: <20170518003210.363A63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2aff91759862df225a14887dafde2766af7c70ea/ghc >--------------------------------------------------------------- commit 2aff91759862df225a14887dafde2766af7c70ea Author: Ben Gamari Date: Wed May 17 20:20:55 2017 -0400 Refactoring >--------------------------------------------------------------- 2aff91759862df225a14887dafde2766af7c70ea Jenkinsfile | 48 +++++++++++++++++++++++++++++++++++++++--------- 1 file changed, 39 insertions(+), 9 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index b661917..33dddb3 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,20 +1,50 @@ +def buildGhc() { + steps { + sh 'git submodule update --init --recursive' + def speed = 'NORMAL' + if (params.nightly) { + speed = 'SLOW' + } + writeFile 'mk/build.mk' + ''' + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + ''' + sh ''' + ./boot + ./configure --enable-tarballs-autodownload + make THREADS=${params.threads} test + ''' + } +} + pipeline { agent any parameters { - booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), - string(name: 'THREADS', defaultValue: '2', description: 'available parallelism') + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') + string(name: 'threads', defaultValue: '2', description: 'available parallelism') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') } stages { stage('Build') { + buildGhc() + } + + stage('Normal testsuite run') { + when { environment name: 'nightly', value: false } + steps { + sh 'make THREADS=${params.threads} test' + } + } + + stage('Slow testsuite run') { + when { environment name: 'nightly', value: true } steps { - sh 'git submodule update --init --recursive' - sh ''' - ./boot - ./configure --enable-tarballs-autodownload - make -j$THREADS - make THREADS=$THREADS test - ''' + sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' + sh 'make THREADS=${params.threads} slowtest' } } } From git at git.haskell.org Thu May 18 00:33:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 00:33:46 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring (41bb855) Message-ID: <20170518003346.55FF83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/41bb8551893d5628a27da01c4f1a11e0c69ec791/ghc >--------------------------------------------------------------- commit 41bb8551893d5628a27da01c4f1a11e0c69ec791 Author: Ben Gamari Date: Wed May 17 20:20:55 2017 -0400 Refactoring >--------------------------------------------------------------- 41bb8551893d5628a27da01c4f1a11e0c69ec791 Jenkinsfile | 50 +++++++++++++++++++++++++++++++++++++++++--------- 1 file changed, 41 insertions(+), 9 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index b661917..ae098de 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,20 +1,52 @@ +def buildGhc() { + steps { + sh 'git submodule update --init --recursive' + def speed = 'NORMAL' + if (params.nightly) { + speed = 'SLOW' + } + writeFile 'mk/build.mk' + ''' + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + ''' + sh ''' + ./boot + ./configure --enable-tarballs-autodownload + make THREADS=${params.threads} test + ''' + } +} + pipeline { agent any parameters { - booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), - string(name: 'THREADS', defaultValue: '2', description: 'available parallelism') + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') + string(name: 'threads', defaultValue: '2', description: 'available parallelism') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') } stages { stage('Build') { steps { - sh 'git submodule update --init --recursive' - sh ''' - ./boot - ./configure --enable-tarballs-autodownload - make -j$THREADS - make THREADS=$THREADS test - ''' + buildGhc() + } + } + + stage('Normal testsuite run') { + when { environment name: 'nightly', value: false } + steps { + sh 'make THREADS=${params.threads} test' + } + } + + stage('Slow testsuite run') { + when { environment name: 'nightly', value: true } + steps { + sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' + sh 'make THREADS=${params.threads} slowtest' } } } From git at git.haskell.org Thu May 18 00:39:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 00:39:11 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring (8932c44) Message-ID: <20170518003911.4C5C63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/8932c44d6c397eab5dba321141af15e846c15a6a/ghc >--------------------------------------------------------------- commit 8932c44d6c397eab5dba321141af15e846c15a6a Author: Ben Gamari Date: Wed May 17 20:20:55 2017 -0400 Refactoring >--------------------------------------------------------------- 8932c44d6c397eab5dba321141af15e846c15a6a Jenkinsfile | 52 +++++++++++++++++++++++++++++++++++++++++++--------- 1 file changed, 43 insertions(+), 9 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index b661917..0fc469a 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,20 +1,54 @@ +def buildGhc() { + steps { + sh 'git submodule update --init --recursive' + def speed = 'NORMAL' + if (params.nightly) { + speed = 'SLOW' + } + writeFile 'mk/build.mk' + ''' + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + ''' + sh ''' + ./boot + ./configure --enable-tarballs-autodownload + make THREADS=${params.threads} test + ''' + } +} + pipeline { agent any parameters { - booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), - string(name: 'THREADS', defaultValue: '2', description: 'available parallelism') + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') + string(name: 'threads', defaultValue: '2', description: 'available parallelism') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') } stages { stage('Build') { steps { - sh 'git submodule update --init --recursive' - sh ''' - ./boot - ./configure --enable-tarballs-autodownload - make -j$THREADS - make THREADS=$THREADS test - ''' + buildGhc() + } + } + + stage('Install testsuite dependencies') { + when { environment expression { return params.nightly } } + steps { + sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' + } + } + + stage('Normal testsuite run') { + steps { + def target = 'test' + if (params.nightly) { + target = 'slowtest' + } + sh 'make THREADS=${params.threads} ${target}' } } } From git at git.haskell.org Thu May 18 00:41:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 00:41:31 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring (8416380) Message-ID: <20170518004131.72A743A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/8416380df163e16ba537a8d12351ca9ae7c7c3ca/ghc >--------------------------------------------------------------- commit 8416380df163e16ba537a8d12351ca9ae7c7c3ca Author: Ben Gamari Date: Wed May 17 20:20:55 2017 -0400 Refactoring >--------------------------------------------------------------- 8416380df163e16ba537a8d12351ca9ae7c7c3ca Jenkinsfile | 52 +++++++++++++++++++++++++++++++++++++++++++--------- 1 file changed, 43 insertions(+), 9 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index b661917..24c2949 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,20 +1,54 @@ +def buildGhc() { + steps { + sh 'git submodule update --init --recursive' + def speed = 'NORMAL' + if (params.nightly) { + speed = 'SLOW' + } + writeFile 'mk/build.mk' + ''' + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + ''' + sh ''' + ./boot + ./configure --enable-tarballs-autodownload + make THREADS=${params.threads} test + ''' + } +} + pipeline { agent any parameters { - booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), - string(name: 'THREADS', defaultValue: '2', description: 'available parallelism') + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') + string(name: 'threads', defaultValue: '2', description: 'available parallelism') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') } stages { stage('Build') { steps { - sh 'git submodule update --init --recursive' - sh ''' - ./boot - ./configure --enable-tarballs-autodownload - make -j$THREADS - make THREADS=$THREADS test - ''' + buildGhc() + } + } + + stage('Install testsuite dependencies') { + when { environment expression { return params.nightly } } + steps { + sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' + } + } + + stage('Normal testsuite run') { + def target = 'test' + if (params.nightly) { + target = 'slowtest' + } + steps { + sh 'make THREADS=${params.threads} ${target}' } } } From git at git.haskell.org Thu May 18 00:53:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 00:53:12 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Move to scripted pipeline (412efb2) Message-ID: <20170518005312.69C033A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/412efb210f1035d9ef53cf3118eab8aee962e0c1/ghc >--------------------------------------------------------------- commit 412efb210f1035d9ef53cf3118eab8aee962e0c1 Author: Ben Gamari Date: Wed May 17 20:52:58 2017 -0400 Move to scripted pipeline >--------------------------------------------------------------- 412efb210f1035d9ef53cf3118eab8aee962e0c1 Jenkinsfile | 60 +++++++++++++++++++++++++++++++----------------------------- 1 file changed, 31 insertions(+), 29 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 24c2949..b87d1dd 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,37 +1,35 @@ -def buildGhc() { - steps { - sh 'git submodule update --init --recursive' - def speed = 'NORMAL' - if (params.nightly) { - speed = 'SLOW' - } - writeFile 'mk/build.mk' - ''' - Validating=YES - ValidateSpeed=${speed} - ValidateHpc=NO - BUILD_DPH=NO - ''' - sh ''' - ./boot - ./configure --enable-tarballs-autodownload - make THREADS=${params.threads} test - ''' - } -} +#!groovy -pipeline { - agent any - parameters { - booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') - string(name: 'threads', defaultValue: '2', description: 'available parallelism') - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') - } +properties( + [ + parameters( + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') + string(name: 'threads', defaultValue: '2', description: 'available parallelism') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + ) + ]) +def buildGhc() { stages { stage('Build') { steps { - buildGhc() + sh 'git submodule update --init --recursive' + def speed = 'NORMAL' + if (params.nightly) { + speed = 'SLOW' + } + writeFile 'mk/build.mk' + ''' + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + ''' + sh ''' + ./boot + ./configure --enable-tarballs-autodownload + make THREADS=${params.threads} test + ''' } } @@ -53,3 +51,7 @@ pipeline { } } } + +node { + buildGhc() +} From git at git.haskell.org Thu May 18 00:54:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 00:54:16 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Move to scripted pipeline (46e83d1) Message-ID: <20170518005416.52C2A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/46e83d1bebe4093073abe3a6cc835d9cb37f8c08/ghc >--------------------------------------------------------------- commit 46e83d1bebe4093073abe3a6cc835d9cb37f8c08 Author: Ben Gamari Date: Wed May 17 20:52:58 2017 -0400 Move to scripted pipeline >--------------------------------------------------------------- 46e83d1bebe4093073abe3a6cc835d9cb37f8c08 Jenkinsfile | 61 ++++++++++++++++++++++++++++++++----------------------------- 1 file changed, 32 insertions(+), 29 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 24c2949..690a8b2 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,37 +1,36 @@ -def buildGhc() { - steps { - sh 'git submodule update --init --recursive' - def speed = 'NORMAL' - if (params.nightly) { - speed = 'SLOW' - } - writeFile 'mk/build.mk' - ''' - Validating=YES - ValidateSpeed=${speed} - ValidateHpc=NO - BUILD_DPH=NO - ''' - sh ''' - ./boot - ./configure --enable-tarballs-autodownload - make THREADS=${params.threads} test - ''' - } -} +#!groovy -pipeline { - agent any - parameters { - booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') - string(name: 'threads', defaultValue: '2', description: 'available parallelism') - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') - } +properties( + [ + parameters( + [ + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') + string(name: 'threads', defaultValue: '2', description: 'available parallelism') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + ]) + ]) +def buildGhc() { stages { stage('Build') { steps { - buildGhc() + sh 'git submodule update --init --recursive' + def speed = 'NORMAL' + if (params.nightly) { + speed = 'SLOW' + } + writeFile 'mk/build.mk' + ''' + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + ''' + sh ''' + ./boot + ./configure --enable-tarballs-autodownload + make THREADS=${params.threads} test + ''' } } @@ -53,3 +52,7 @@ pipeline { } } } + +node { + buildGhc() +} From git at git.haskell.org Thu May 18 01:03:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 01:03:04 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Move to scripted pipeline (84f6197) Message-ID: <20170518010304.9B8083A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/84f6197b0e044bae917bbbdec23ba634b33cc490/ghc >--------------------------------------------------------------- commit 84f6197b0e044bae917bbbdec23ba634b33cc490 Author: Ben Gamari Date: Wed May 17 20:52:58 2017 -0400 Move to scripted pipeline >--------------------------------------------------------------- 84f6197b0e044bae917bbbdec23ba634b33cc490 Jenkinsfile | 61 ++++++++++++++++++++++++++++++++----------------------------- 1 file changed, 32 insertions(+), 29 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 24c2949..7b91572 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,37 +1,36 @@ -def buildGhc() { - steps { - sh 'git submodule update --init --recursive' - def speed = 'NORMAL' - if (params.nightly) { - speed = 'SLOW' - } - writeFile 'mk/build.mk' - ''' - Validating=YES - ValidateSpeed=${speed} - ValidateHpc=NO - BUILD_DPH=NO - ''' - sh ''' - ./boot - ./configure --enable-tarballs-autodownload - make THREADS=${params.threads} test - ''' - } -} +#!groovy -pipeline { - agent any - parameters { - booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') - string(name: 'threads', defaultValue: '2', description: 'available parallelism') - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') - } +properties( + [ + parameters( + [ + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), + string(name: 'threads', defaultValue: '2', description: 'available parallelism'), + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + ]) + ]) +def buildGhc() { stages { stage('Build') { steps { - buildGhc() + sh 'git submodule update --init --recursive' + def speed = 'NORMAL' + if (params.nightly) { + speed = 'SLOW' + } + writeFile 'mk/build.mk' + ''' + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + ''' + sh ''' + ./boot + ./configure --enable-tarballs-autodownload + make THREADS=${params.threads} test + ''' } } @@ -53,3 +52,7 @@ pipeline { } } } + +node { + buildGhc() +} From git at git.haskell.org Thu May 18 01:04:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 01:04:51 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Move to scripted pipeline (6d8dcc7) Message-ID: <20170518010451.292653A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/6d8dcc7c50990316bea9f4fcb99b01a0b063867c/ghc >--------------------------------------------------------------- commit 6d8dcc7c50990316bea9f4fcb99b01a0b063867c Author: Ben Gamari Date: Wed May 17 20:52:58 2017 -0400 Move to scripted pipeline >--------------------------------------------------------------- 6d8dcc7c50990316bea9f4fcb99b01a0b063867c Jenkinsfile | 91 +++++++++++++++++++++++++++++++------------------------------ 1 file changed, 46 insertions(+), 45 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 24c2949..5fb3a19 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,55 +1,56 @@ -def buildGhc() { - steps { - sh 'git submodule update --init --recursive' - def speed = 'NORMAL' - if (params.nightly) { - speed = 'SLOW' - } - writeFile 'mk/build.mk' - ''' - Validating=YES - ValidateSpeed=${speed} - ValidateHpc=NO - BUILD_DPH=NO - ''' - sh ''' - ./boot - ./configure --enable-tarballs-autodownload - make THREADS=${params.threads} test - ''' - } -} +#!groovy -pipeline { - agent any - parameters { - booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') - string(name: 'threads', defaultValue: '2', description: 'available parallelism') - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') - } +properties( + [ + parameters( + [ + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), + string(name: 'threads', defaultValue: '2', description: 'available parallelism'), + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + ]) + ]) - stages { - stage('Build') { - steps { - buildGhc() +def buildGhc() { + stage('Build') { + steps { + sh 'git submodule update --init --recursive' + def speed = 'NORMAL' + if (params.nightly) { + speed = 'SLOW' } + writeFile 'mk/build.mk' + ''' + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + ''' + sh ''' + ./boot + ./configure --enable-tarballs-autodownload + make THREADS=${params.threads} test + ''' } + } - stage('Install testsuite dependencies') { - when { environment expression { return params.nightly } } - steps { - sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' - } + stage('Install testsuite dependencies') { + when { environment expression { return params.nightly } } + steps { + sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' } + } - stage('Normal testsuite run') { - def target = 'test' - if (params.nightly) { - target = 'slowtest' - } - steps { - sh 'make THREADS=${params.threads} ${target}' - } + stage('Normal testsuite run') { + def target = 'test' + if (params.nightly) { + target = 'slowtest' + } + steps { + sh 'make THREADS=${params.threads} ${target}' } } } + +node { + buildGhc() +} From git at git.haskell.org Thu May 18 01:08:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 01:08:50 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Move to scripted pipeline (fb0854f) Message-ID: <20170518010850.4F9DD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/fb0854f2fe06d0243dd55cde5ee99dc528f60e44/ghc >--------------------------------------------------------------- commit fb0854f2fe06d0243dd55cde5ee99dc528f60e44 Author: Ben Gamari Date: Wed May 17 20:52:58 2017 -0400 Move to scripted pipeline >--------------------------------------------------------------- fb0854f2fe06d0243dd55cde5ee99dc528f60e44 Jenkinsfile | 56 ++++++++++++++++++++++++++------------------------------ 1 file changed, 26 insertions(+), 30 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 24c2949..184e94a 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,5 +1,17 @@ +#!groovy + +properties( + [ + parameters( + [ + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), + string(name: 'threads', defaultValue: '2', description: 'available parallelism'), + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + ]) + ]) + def buildGhc() { - steps { + stage('Build') { sh 'git submodule update --init --recursive' def speed = 'NORMAL' if (params.nightly) { @@ -18,38 +30,22 @@ def buildGhc() { make THREADS=${params.threads} test ''' } -} - -pipeline { - agent any - parameters { - booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') - string(name: 'threads', defaultValue: '2', description: 'available parallelism') - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') - } - - stages { - stage('Build') { - steps { - buildGhc() - } - } - stage('Install testsuite dependencies') { - when { environment expression { return params.nightly } } - steps { - sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' - } + stage('Install testsuite dependencies') { + if (params.nightly) { + sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' } + } - stage('Normal testsuite run') { - def target = 'test' - if (params.nightly) { - target = 'slowtest' - } - steps { - sh 'make THREADS=${params.threads} ${target}' - } + stage('Normal testsuite run') { + def target = 'test' + if (params.nightly) { + target = 'slowtest' } + sh 'make THREADS=${params.threads} ${target}' } } + +node { + buildGhc() +} From git at git.haskell.org Thu May 18 01:10:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 01:10:47 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Move to scripted pipeline (2262812) Message-ID: <20170518011047.891293A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2262812fa463adfc9d55061394a13f1c70b55df9/ghc >--------------------------------------------------------------- commit 2262812fa463adfc9d55061394a13f1c70b55df9 Author: Ben Gamari Date: Wed May 17 20:52:58 2017 -0400 Move to scripted pipeline >--------------------------------------------------------------- 2262812fa463adfc9d55061394a13f1c70b55df9 Jenkinsfile | 71 +++++++++++++++++++++++++++++-------------------------------- 1 file changed, 34 insertions(+), 37 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 24c2949..33596ba 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,55 +1,52 @@ +#!groovy + +properties( + [ + parameters( + [ + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), + string(name: 'threads', defaultValue: '2', description: 'available parallelism'), + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + ]) + ]) + def buildGhc() { - steps { + stage('Build') { sh 'git submodule update --init --recursive' def speed = 'NORMAL' if (params.nightly) { speed = 'SLOW' } - writeFile 'mk/build.mk' - ''' - Validating=YES - ValidateSpeed=${speed} - ValidateHpc=NO - BUILD_DPH=NO - ''' + writeFile( + file: 'mk/build.mk' + text: ''' + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + ''') sh ''' ./boot ./configure --enable-tarballs-autodownload make THREADS=${params.threads} test ''' } -} - -pipeline { - agent any - parameters { - booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') - string(name: 'threads', defaultValue: '2', description: 'available parallelism') - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') - } - - stages { - stage('Build') { - steps { - buildGhc() - } - } - stage('Install testsuite dependencies') { - when { environment expression { return params.nightly } } - steps { - sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' - } + stage('Install testsuite dependencies') { + if (params.nightly) { + sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' } + } - stage('Normal testsuite run') { - def target = 'test' - if (params.nightly) { - target = 'slowtest' - } - steps { - sh 'make THREADS=${params.threads} ${target}' - } + stage('Normal testsuite run') { + def target = 'test' + if (params.nightly) { + target = 'slowtest' } + sh 'make THREADS=${params.threads} ${target}' } } + +node { + buildGhc() +} From git at git.haskell.org Thu May 18 01:11:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 01:11:21 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Move to scripted pipeline (59c46fe) Message-ID: <20170518011121.6B6503A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/59c46fea66d3c770fdfdf868ad780cd07a932d60/ghc >--------------------------------------------------------------- commit 59c46fea66d3c770fdfdf868ad780cd07a932d60 Author: Ben Gamari Date: Wed May 17 20:52:58 2017 -0400 Move to scripted pipeline >--------------------------------------------------------------- 59c46fea66d3c770fdfdf868ad780cd07a932d60 Jenkinsfile | 71 +++++++++++++++++++++++++++++-------------------------------- 1 file changed, 34 insertions(+), 37 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 24c2949..7241d90 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,55 +1,52 @@ +#!groovy + +properties( + [ + parameters( + [ + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), + string(name: 'threads', defaultValue: '2', description: 'available parallelism'), + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + ]) + ]) + def buildGhc() { - steps { + stage('Build') { sh 'git submodule update --init --recursive' def speed = 'NORMAL' if (params.nightly) { speed = 'SLOW' } - writeFile 'mk/build.mk' - ''' - Validating=YES - ValidateSpeed=${speed} - ValidateHpc=NO - BUILD_DPH=NO - ''' + writeFile( + file: 'mk/build.mk', + text: ''' + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + ''') sh ''' ./boot ./configure --enable-tarballs-autodownload make THREADS=${params.threads} test ''' } -} - -pipeline { - agent any - parameters { - booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') - string(name: 'threads', defaultValue: '2', description: 'available parallelism') - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') - } - - stages { - stage('Build') { - steps { - buildGhc() - } - } - stage('Install testsuite dependencies') { - when { environment expression { return params.nightly } } - steps { - sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' - } + stage('Install testsuite dependencies') { + if (params.nightly) { + sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' } + } - stage('Normal testsuite run') { - def target = 'test' - if (params.nightly) { - target = 'slowtest' - } - steps { - sh 'make THREADS=${params.threads} ${target}' - } + stage('Normal testsuite run') { + def target = 'test' + if (params.nightly) { + target = 'slowtest' } + sh 'make THREADS=${params.threads} ${target}' } } + +node { + buildGhc() +} From git at git.haskell.org Thu May 18 01:38:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 01:38:22 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Move to scripted pipeline (76855fe) Message-ID: <20170518013822.B27A63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/76855fea5c5fbf3f733b49d87e6b79ebddb1c49b/ghc >--------------------------------------------------------------- commit 76855fea5c5fbf3f733b49d87e6b79ebddb1c49b Author: Ben Gamari Date: Wed May 17 20:52:58 2017 -0400 Move to scripted pipeline >--------------------------------------------------------------- 76855fea5c5fbf3f733b49d87e6b79ebddb1c49b Jenkinsfile | 81 +++++++++++++++++++++++++++++-------------------------------- 1 file changed, 39 insertions(+), 42 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 24c2949..44c1dc0 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,55 +1,52 @@ +#!groovy + +properties( + [ + parameters( + [ + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), + string(name: 'threads', defaultValue: '2', description: 'available parallelism'), + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + ]) + ]) + def buildGhc() { - steps { + stage('Build') { sh 'git submodule update --init --recursive' def speed = 'NORMAL' if (params.nightly) { speed = 'SLOW' } - writeFile 'mk/build.mk' - ''' - Validating=YES - ValidateSpeed=${speed} - ValidateHpc=NO - BUILD_DPH=NO - ''' - sh ''' - ./boot - ./configure --enable-tarballs-autodownload - make THREADS=${params.threads} test - ''' - } -} - -pipeline { - agent any - parameters { - booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') - string(name: 'threads', defaultValue: '2', description: 'available parallelism') - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + writeFile( + file: 'mk/build.mk', + text: """ + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + """) + sh """ + ./boot + ./configure --enable-tarballs-autodownload + make THREADS=${params.threads} test + """ } - stages { - stage('Build') { - steps { - buildGhc() - } - } - - stage('Install testsuite dependencies') { - when { environment expression { return params.nightly } } - steps { - sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' - } + stage('Install testsuite dependencies') { + if (params.nightly) { + sh "cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector" } + } - stage('Normal testsuite run') { - def target = 'test' - if (params.nightly) { - target = 'slowtest' - } - steps { - sh 'make THREADS=${params.threads} ${target}' - } + stage('Normal testsuite run') { + def target = 'test' + if (params.nightly) { + target = 'slowtest' } + sh "make THREADS=${params.threads} ${target}" } } + +node { + buildGhc() +} From git at git.haskell.org Thu May 18 01:39:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 01:39:32 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Move to scripted pipeline (9105c84) Message-ID: <20170518013932.D09BA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9105c84a482f7c9fa86242bc91274237c7ba4563/ghc >--------------------------------------------------------------- commit 9105c84a482f7c9fa86242bc91274237c7ba4563 Author: Ben Gamari Date: Wed May 17 20:52:58 2017 -0400 Move to scripted pipeline >--------------------------------------------------------------- 9105c84a482f7c9fa86242bc91274237c7ba4563 Jenkinsfile | 81 +++++++++++++++++++++++++++++-------------------------------- 1 file changed, 39 insertions(+), 42 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 24c2949..622c171 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,55 +1,52 @@ +#!groovy + +properties( + [ + parameters( + [ + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), + string(name: 'threads', defaultValue: '2', description: 'available parallelism'), + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + ]) + ]) + def buildGhc() { - steps { + stage('Build') { sh 'git submodule update --init --recursive' def speed = 'NORMAL' if (params.nightly) { speed = 'SLOW' } - writeFile 'mk/build.mk' - ''' - Validating=YES - ValidateSpeed=${speed} - ValidateHpc=NO - BUILD_DPH=NO - ''' - sh ''' - ./boot - ./configure --enable-tarballs-autodownload - make THREADS=${params.threads} test - ''' - } -} - -pipeline { - agent any - parameters { - booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') - string(name: 'threads', defaultValue: '2', description: 'available parallelism') - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + writeFile( + file: 'mk/build.mk', + text: """ + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + """) + sh """ + ./boot + ./configure --enable-tarballs-autodownload + make -j${params.threads} + """ } - stages { - stage('Build') { - steps { - buildGhc() - } - } - - stage('Install testsuite dependencies') { - when { environment expression { return params.nightly } } - steps { - sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' - } + stage('Install testsuite dependencies') { + if (params.nightly) { + sh "cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector" } + } - stage('Normal testsuite run') { - def target = 'test' - if (params.nightly) { - target = 'slowtest' - } - steps { - sh 'make THREADS=${params.threads} ${target}' - } + stage('Normal testsuite run') { + def target = 'test' + if (params.nightly) { + target = 'slowtest' } + sh "make THREADS=${params.threads} ${target}" } } + +node { + buildGhc() +} From git at git.haskell.org Thu May 18 01:47:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 01:47:43 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Move to scripted pipeline (633f254) Message-ID: <20170518014743.ADA273A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/633f2542adef73e5b3a97ca75f9fe183fb7015eb/ghc >--------------------------------------------------------------- commit 633f2542adef73e5b3a97ca75f9fe183fb7015eb Author: Ben Gamari Date: Wed May 17 20:52:58 2017 -0400 Move to scripted pipeline >--------------------------------------------------------------- 633f2542adef73e5b3a97ca75f9fe183fb7015eb Jenkinsfile | 83 ++++++++++++++++++++++++++++++------------------------------- 1 file changed, 41 insertions(+), 42 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 24c2949..ee92071 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,55 +1,54 @@ +#!groovy + +properties( + [ + parameters( + [ + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + ]) + ]) + def buildGhc() { - steps { + stage('Build') { sh 'git submodule update --init --recursive' def speed = 'NORMAL' if (params.nightly) { speed = 'SLOW' } - writeFile 'mk/build.mk' - ''' - Validating=YES - ValidateSpeed=${speed} - ValidateHpc=NO - BUILD_DPH=NO - ''' - sh ''' - ./boot - ./configure --enable-tarballs-autodownload - make THREADS=${params.threads} test - ''' - } -} - -pipeline { - agent any - parameters { - booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') - string(name: 'threads', defaultValue: '2', description: 'available parallelism') - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + writeFile( + file: 'mk/build.mk', + text: """ + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + """) + sh """ + ./boot + ./configure --enable-tarballs-autodownload + make -j${env.THREADS} + """ } - stages { - stage('Build') { - steps { - buildGhc() - } - } - - stage('Install testsuite dependencies') { - when { environment expression { return params.nightly } } - steps { - sh 'cabal install --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d mtl parallel parsec primitive QuickCheck random regex-compat syb stm utf8-string vector' - } + stage('Install testsuite dependencies') { + if (params.nightly) { + def pkgs = ['mtl', 'parallel', 'parsec', 'primitive', 'QuickCheck', + 'random', 'regex-compat', 'syb', 'stm', 'utf8-string', + 'vector'] + sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } + } - stage('Normal testsuite run') { - def target = 'test' - if (params.nightly) { - target = 'slowtest' - } - steps { - sh 'make THREADS=${params.threads} ${target}' - } + stage('Normal testsuite run') { + def target = 'test' + if (params.nightly) { + target = 'slowtest' } + sh "make THREADS=${env.THREADS} ${target}" } } + +node { + buildGhc() +} From git at git.haskell.org Thu May 18 02:41:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 02:41:19 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add nofib, bindist, and aarch64 support (363b552) Message-ID: <20170518024119.019B03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/363b552b142c6981d3411a9bc816dc9d7d835313/ghc >--------------------------------------------------------------- commit 363b552b142c6981d3411a9bc816dc9d7d835313 Author: Ben Gamari Date: Wed May 17 22:41:02 2017 -0400 Add nofib, bindist, and aarch64 support >--------------------------------------------------------------- 363b552b142c6981d3411a9bc816dc9d7d835313 Jenkinsfile | 29 ++++++++++++++++++++++++----- 1 file changed, 24 insertions(+), 5 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index ee92071..0fe0185 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -6,10 +6,12 @@ properties( [ booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + booleanParam(name: 'buildBindist', defaultValue: false, description: 'prepare and archive a binary distribution?') + booleanParam(name: 'runNofib', defaultValue: false, description: 'run nofib and archive results') ]) ]) -def buildGhc() { +def buildGhc(boolean runNofib=false) { stage('Build') { sh 'git submodule update --init --recursive' def speed = 'NORMAL' @@ -40,15 +42,32 @@ def buildGhc() { } } - stage('Normal testsuite run') { + stage('Run testsuite') { def target = 'test' if (params.nightly) { target = 'slowtest' } sh "make THREADS=${env.THREADS} ${target}" } -} -node { - buildGhc() + stage('Run nofib') { + if (runNofib) { + sh """ + cd nofib + make boot + make >../nofib.log 2>&1 + """ + archive 'nofib.log' + } + } + + stage('Prepare bindist') { + if (params.buildBindist) { + sh "make binary-dist" + archive 'ghc-*.tar.xz' + } + } } + +node { buildGhc(runNofib: params.runNofib) } +node(label: 'aarch64') { buildGhc() } From git at git.haskell.org Thu May 18 02:44:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 02:44:58 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add nofib, bindist, and aarch64 support (b6a2234) Message-ID: <20170518024458.BDBA13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/b6a223433f96a4831b8a16deb18f72a185d005fd/ghc >--------------------------------------------------------------- commit b6a223433f96a4831b8a16deb18f72a185d005fd Author: Ben Gamari Date: Wed May 17 22:41:02 2017 -0400 Add nofib, bindist, and aarch64 support >--------------------------------------------------------------- b6a223433f96a4831b8a16deb18f72a185d005fd Jenkinsfile | 31 +++++++++++++++++++++++++------ 1 file changed, 25 insertions(+), 6 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index ee92071..b29e8b7 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -5,11 +5,13 @@ properties( parameters( [ booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?'), + booleanParam(name: 'buildBindist', defaultValue: false, description: 'prepare and archive a binary distribution?'), + booleanParam(name: 'runNofib', defaultValue: false, description: 'run nofib and archive results') ]) ]) -def buildGhc() { +def buildGhc(boolean runNofib=false) { stage('Build') { sh 'git submodule update --init --recursive' def speed = 'NORMAL' @@ -40,15 +42,32 @@ def buildGhc() { } } - stage('Normal testsuite run') { + stage('Run testsuite') { def target = 'test' if (params.nightly) { target = 'slowtest' } sh "make THREADS=${env.THREADS} ${target}" } -} -node { - buildGhc() + stage('Run nofib') { + if (runNofib) { + sh """ + cd nofib + make boot + make >../nofib.log 2>&1 + """ + archive 'nofib.log' + } + } + + stage('Prepare bindist') { + if (params.buildBindist) { + sh "make binary-dist" + archive 'ghc-*.tar.xz' + } + } } + +node { buildGhc(runNofib: params.runNofib) } +node(label: 'aarch64') { buildGhc() } From git at git.haskell.org Thu May 18 02:47:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 02:47:36 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add nofib, bindist, and aarch64 support (a2a6fb8) Message-ID: <20170518024736.018FB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a2a6fb8de85434a32f1286a17fa013b525780634/ghc >--------------------------------------------------------------- commit a2a6fb8de85434a32f1286a17fa013b525780634 Author: Ben Gamari Date: Wed May 17 22:41:02 2017 -0400 Add nofib, bindist, and aarch64 support >--------------------------------------------------------------- a2a6fb8de85434a32f1286a17fa013b525780634 Jenkinsfile | 31 +++++++++++++++++++++++++------ 1 file changed, 25 insertions(+), 6 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index ee92071..20da5c2 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -5,11 +5,13 @@ properties( parameters( [ booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?'), + booleanParam(name: 'buildBindist', defaultValue: false, description: 'prepare and archive a binary distribution?'), + booleanParam(name: 'runNofib', defaultValue: false, description: 'run nofib and archive results') ]) ]) -def buildGhc() { +def buildGhc(boolean runNofib=false) { stage('Build') { sh 'git submodule update --init --recursive' def speed = 'NORMAL' @@ -40,15 +42,32 @@ def buildGhc() { } } - stage('Normal testsuite run') { + stage('Run testsuite') { def target = 'test' if (params.nightly) { target = 'slowtest' } sh "make THREADS=${env.THREADS} ${target}" } -} -node { - buildGhc() + stage('Run nofib') { + if (runNofib) { + sh """ + cd nofib + make boot + make >../nofib.log 2>&1 + """ + archive 'nofib.log' + } + } + + stage('Prepare bindist') { + if (params.buildBindist) { + sh "make binary-dist" + archive 'ghc-*.tar.xz' + } + } } + +node { buildGhc(runNofib: params.runNofib) } +///node(label: 'aarch64') { buildGhc() } From git at git.haskell.org Thu May 18 02:48:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 02:48:28 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add nofib, bindist, and aarch64 support (fae8b07) Message-ID: <20170518024828.39F293A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/fae8b076d1c8fe46684f5b5afde91d10766074d6/ghc >--------------------------------------------------------------- commit fae8b076d1c8fe46684f5b5afde91d10766074d6 Author: Ben Gamari Date: Wed May 17 22:41:02 2017 -0400 Add nofib, bindist, and aarch64 support >--------------------------------------------------------------- fae8b076d1c8fe46684f5b5afde91d10766074d6 Jenkinsfile | 29 ++++++++++++++++++++++++----- 1 file changed, 24 insertions(+), 5 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index ee92071..f1837fb 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -5,7 +5,9 @@ properties( parameters( [ booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?'), + booleanParam(name: 'buildBindist', defaultValue: false, description: 'prepare and archive a binary distribution?'), + booleanParam(name: 'runNofib', defaultValue: false, description: 'run nofib and archive results') ]) ]) @@ -40,15 +42,32 @@ def buildGhc() { } } - stage('Normal testsuite run') { + stage('Run testsuite') { def target = 'test' if (params.nightly) { target = 'slowtest' } sh "make THREADS=${env.THREADS} ${target}" } -} -node { - buildGhc() + stage('Run nofib') { + if (runNofib) { + sh """ + cd nofib + make boot + make >../nofib.log 2>&1 + """ + archive 'nofib.log' + } + } + + stage('Prepare bindist') { + if (params.buildBindist) { + sh "make binary-dist" + archive 'ghc-*.tar.xz' + } + } } + +///node { buildGhc(runNofib: params.runNofib) } +node(label: 'aarch64') { buildGhc() } From git at git.haskell.org Thu May 18 02:49:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 02:49:32 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add nofib, bindist, and aarch64 support (8485282) Message-ID: <20170518024932.0D1453A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/8485282e87165d67f4d51099ef5e81b0010df396/ghc >--------------------------------------------------------------- commit 8485282e87165d67f4d51099ef5e81b0010df396 Author: Ben Gamari Date: Wed May 17 22:41:02 2017 -0400 Add nofib, bindist, and aarch64 support >--------------------------------------------------------------- 8485282e87165d67f4d51099ef5e81b0010df396 Jenkinsfile | 27 ++++++++++++++++++++++++--- 1 file changed, 24 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index ee92071..75ecd57 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -5,7 +5,9 @@ properties( parameters( [ booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?'), + booleanParam(name: 'buildBindist', defaultValue: false, description: 'prepare and archive a binary distribution?'), + booleanParam(name: 'runNofib', defaultValue: false, description: 'run nofib and archive results') ]) ]) @@ -40,15 +42,34 @@ def buildGhc() { } } - stage('Normal testsuite run') { + stage('Run testsuite') { def target = 'test' if (params.nightly) { target = 'slowtest' } sh "make THREADS=${env.THREADS} ${target}" } + + stage('Run nofib') { + if (runNofib) { + sh """ + cd nofib + make boot + make >../nofib.log 2>&1 + """ + archive 'nofib.log' + } + } + + stage('Prepare bindist') { + if (params.buildBindist) { + sh "make binary-dist" + archive 'ghc-*.tar.xz' + } + } } -node { +//node { buildGhc(runNofib: params.runNofib) } +node(label: 'aarch64') { buildGhc() } From git at git.haskell.org Thu May 18 02:55:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 02:55:49 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add nofib, bindist, and aarch64 support (1b9426a) Message-ID: <20170518025549.2D0173A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/1b9426ad04654e95ce138a7bba7b89987dc24e64/ghc >--------------------------------------------------------------- commit 1b9426ad04654e95ce138a7bba7b89987dc24e64 Author: Ben Gamari Date: Wed May 17 22:41:02 2017 -0400 Add nofib, bindist, and aarch64 support >--------------------------------------------------------------- 1b9426ad04654e95ce138a7bba7b89987dc24e64 Jenkinsfile | 30 +++++++++++++++++++++++++++--- 1 file changed, 27 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index ee92071..c1b7c06 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -5,7 +5,9 @@ properties( parameters( [ booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?'), + booleanParam(name: 'buildBindist', defaultValue: false, description: 'prepare and archive a binary distribution?'), + booleanParam(name: 'runNofib', defaultValue: false, description: 'run nofib and archive results') ]) ]) @@ -40,15 +42,37 @@ def buildGhc() { } } - stage('Normal testsuite run') { + stage('Run testsuite') { def target = 'test' if (params.nightly) { target = 'slowtest' } sh "make THREADS=${env.THREADS} ${target}" } + + stage('Run nofib') { + if (runNofib) { + sh """ + cd nofib + make boot + make >../nofib.log 2>&1 + """ + archive 'nofib.log' + } + } + + stage('Prepare bindist') { + if (params.buildBindist) { + sh "make binary-dist" + archive 'ghc-*.tar.xz' + } + } } -node { +//node { buildGhc(runNofib: params.runNofib) } +node(label: 'linux && amd64') { + buildGhc() +} +node(label: 'aarch64') { buildGhc() } From git at git.haskell.org Thu May 18 03:14:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 03:14:09 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add nofib, bindist, and aarch64 support (fcf8f84) Message-ID: <20170518031409.B4DED3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/fcf8f84a534c6a59f30baa26e169256f74235471/ghc >--------------------------------------------------------------- commit fcf8f84a534c6a59f30baa26e169256f74235471 Author: Ben Gamari Date: Wed May 17 22:41:02 2017 -0400 Add nofib, bindist, and aarch64 support >--------------------------------------------------------------- fcf8f84a534c6a59f30baa26e169256f74235471 Jenkinsfile | 39 ++++++++++++++++++++++++++++++++++----- 1 file changed, 34 insertions(+), 5 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index ee92071..5201df3 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -5,11 +5,17 @@ properties( parameters( [ booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?'), + booleanParam(name: 'buildBindist', defaultValue: false, description: 'prepare and archive a binary distribution?'), + booleanParam(name: 'runNofib', defaultValue: false, description: 'run nofib and archive results') ]) ]) -def buildGhc() { +def installPackages(pkgs) { + sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" +} + +def buildGhc(runNofib) { stage('Build') { sh 'git submodule update --init --recursive' def speed = 'NORMAL' @@ -36,19 +42,42 @@ def buildGhc() { def pkgs = ['mtl', 'parallel', 'parsec', 'primitive', 'QuickCheck', 'random', 'regex-compat', 'syb', 'stm', 'utf8-string', 'vector'] - sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" + installPkgs pkgs } } - stage('Normal testsuite run') { + stage('Run testsuite') { def target = 'test' if (params.nightly) { target = 'slowtest' } sh "make THREADS=${env.THREADS} ${target}" } + + stage('Run nofib') { + if (runNofib) { + installPkgs(['regex-compat']) + sh """ + cd nofib + make boot + make >../nofib.log 2>&1 + """ + archive 'nofib.log' + } + } + + stage('Prepare bindist') { + if (params.buildBindist) { + sh "make binary-dist" + archive 'ghc-*.tar.xz' + } + } } -node { +//node { buildGhc(runNofib: params.runNofib) } +node(label: 'linux && amd64') { + buildGhc() +} +node(label: 'aarch64') { buildGhc() } From git at git.haskell.org Thu May 18 03:15:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 03:15:26 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add nofib, bindist, and aarch64 support (893a061) Message-ID: <20170518031526.3230D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/893a061cebd83fc108f2d1b036d075486bfbab68/ghc >--------------------------------------------------------------- commit 893a061cebd83fc108f2d1b036d075486bfbab68 Author: Ben Gamari Date: Wed May 17 22:41:02 2017 -0400 Add nofib, bindist, and aarch64 support >--------------------------------------------------------------- 893a061cebd83fc108f2d1b036d075486bfbab68 Jenkinsfile | 43 ++++++++++++++++++++++++++++++++++++------- 1 file changed, 36 insertions(+), 7 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index ee92071..e6c0ae7 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -5,11 +5,25 @@ properties( parameters( [ booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?'), + booleanParam(name: 'buildBindist', defaultValue: false, description: 'prepare and archive a binary distribution?'), + booleanParam(name: 'runNofib', defaultValue: false, description: 'run nofib and archive results') ]) ]) -def buildGhc() { +//node { buildGhc(runNofib: params.runNofib) } +node(label: 'linux && amd64') { + buildGhc() +} +node(label: 'aarch64') { + buildGhc() +} + +def installPackages(pkgs) { + sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" +} + +def buildGhc(runNofib) { stage('Build') { sh 'git submodule update --init --recursive' def speed = 'NORMAL' @@ -36,19 +50,34 @@ def buildGhc() { def pkgs = ['mtl', 'parallel', 'parsec', 'primitive', 'QuickCheck', 'random', 'regex-compat', 'syb', 'stm', 'utf8-string', 'vector'] - sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" + installPkgs pkgs } } - stage('Normal testsuite run') { + stage('Run testsuite') { def target = 'test' if (params.nightly) { target = 'slowtest' } sh "make THREADS=${env.THREADS} ${target}" } -} -node { - buildGhc() + stage('Run nofib') { + if (runNofib) { + installPkgs(['regex-compat']) + sh """ + cd nofib + make boot + make >../nofib.log 2>&1 + """ + archive 'nofib.log' + } + } + + stage('Prepare bindist') { + if (params.buildBindist) { + sh "make binary-dist" + archive 'ghc-*.tar.xz' + } + } } From git at git.haskell.org Thu May 18 03:19:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 03:19:02 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add nofib, bindist, and aarch64 support (95edefe) Message-ID: <20170518031902.CE7563A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/95edefe84d747daa4b343890787bdb241b357b7a/ghc >--------------------------------------------------------------- commit 95edefe84d747daa4b343890787bdb241b357b7a Author: Ben Gamari Date: Wed May 17 22:41:02 2017 -0400 Add nofib, bindist, and aarch64 support >--------------------------------------------------------------- 95edefe84d747daa4b343890787bdb241b357b7a Jenkinsfile | 43 ++++++++++++++++++++++++++++++++++++------- 1 file changed, 36 insertions(+), 7 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index ee92071..c15600e 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -5,11 +5,25 @@ properties( parameters( [ booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?'), + booleanParam(name: 'buildBindist', defaultValue: false, description: 'prepare and archive a binary distribution?'), + booleanParam(name: 'runNofib', defaultValue: false, description: 'run nofib and archive results') ]) ]) -def buildGhc() { +//node { buildGhc(runNofib: params.runNofib) } +node(label: 'linux && amd64') { + buildGhc(false) +} +node(label: 'aarch64') { + buildGhc(false) +} + +def installPackages(pkgs) { + sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" +} + +def buildGhc(runNofib) { stage('Build') { sh 'git submodule update --init --recursive' def speed = 'NORMAL' @@ -36,19 +50,34 @@ def buildGhc() { def pkgs = ['mtl', 'parallel', 'parsec', 'primitive', 'QuickCheck', 'random', 'regex-compat', 'syb', 'stm', 'utf8-string', 'vector'] - sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" + installPkgs pkgs } } - stage('Normal testsuite run') { + stage('Run testsuite') { def target = 'test' if (params.nightly) { target = 'slowtest' } sh "make THREADS=${env.THREADS} ${target}" } -} -node { - buildGhc() + stage('Run nofib') { + if (runNofib) { + installPkgs(['regex-compat']) + sh """ + cd nofib + make boot + make >../nofib.log 2>&1 + """ + archive 'nofib.log' + } + } + + stage('Prepare bindist') { + if (params.buildBindist) { + sh "make binary-dist" + archive 'ghc-*.tar.xz' + } + } } From git at git.haskell.org Thu May 18 03:35:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 03:35:15 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add nofib, bindist, and aarch64 support (4443b02) Message-ID: <20170518033515.7D7FC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/4443b0201efc5d389c84fae0e4cbfc48bcf8dd69/ghc >--------------------------------------------------------------- commit 4443b0201efc5d389c84fae0e4cbfc48bcf8dd69 Author: Ben Gamari Date: Wed May 17 22:41:02 2017 -0400 Add nofib, bindist, and aarch64 support >--------------------------------------------------------------- 4443b0201efc5d389c84fae0e4cbfc48bcf8dd69 Jenkinsfile | 44 +++++++++++++++++++++++++++++++++++++------- 1 file changed, 37 insertions(+), 7 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index ee92071..eada3d5 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -5,11 +5,25 @@ properties( parameters( [ booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), - booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?') + booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?'), + booleanParam(name: 'buildBindist', defaultValue: false, description: 'prepare and archive a binary distribution?'), + booleanParam(name: 'runNofib', defaultValue: false, description: 'run nofib and archive results') ]) ]) -def buildGhc() { +//node { buildGhc(runNofib: params.runNofib) } +node(label: 'linux && amd64') { + buildGhc(false) +} +node(label: 'aarch64') { + buildGhc(false) +} + +def installPackages(pkgs) { + sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" +} + +def buildGhc(runNofib) { stage('Build') { sh 'git submodule update --init --recursive' def speed = 'NORMAL' @@ -36,19 +50,35 @@ def buildGhc() { def pkgs = ['mtl', 'parallel', 'parsec', 'primitive', 'QuickCheck', 'random', 'regex-compat', 'syb', 'stm', 'utf8-string', 'vector'] - sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" + installPkgs pkgs } } - stage('Normal testsuite run') { + stage('Run testsuite') { def target = 'test' if (params.nightly) { target = 'slowtest' } sh "make THREADS=${env.THREADS} ${target}" } -} -node { - buildGhc() + stage('Run nofib') { + if (runNofib) { + installPkgs(['regex-compat']) + sh """ + cd nofib + make clean + make boot + make >../nofib.log 2>&1 + """ + archive 'nofib.log' + } + } + + stage('Prepare bindist') { + if (params.buildBindist) { + sh "make binary-dist" + archive 'ghc-*.tar.xz' + } + } } From git at git.haskell.org Thu May 18 03:35:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 03:35:18 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Run jobs in parallel (3e71418) Message-ID: <20170518033518.3AC833A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/3e71418164695ad5d1037042a88b65d7c02b59dd/ghc >--------------------------------------------------------------- commit 3e71418164695ad5d1037042a88b65d7c02b59dd Author: Ben Gamari Date: Wed May 17 23:34:37 2017 -0400 Run jobs in parallel >--------------------------------------------------------------- 3e71418164695ad5d1037042a88b65d7c02b59dd Jenkinsfile | 22 +++++++++++++--------- 1 file changed, 13 insertions(+), 9 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index eada3d5..eeb8dc6 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,19 +11,23 @@ properties( ]) ]) -//node { buildGhc(runNofib: params.runNofib) } -node(label: 'linux && amd64') { - buildGhc(false) -} -node(label: 'aarch64') { - buildGhc(false) -} +parallel ( + 'linux x86-64': {node(label: 'linux && amd64') {buildGhc(params.runNofib)}} + 'aarch64': {node(label: 'aarch64') {buildGhc(false)}} + 'osx': {node(label: 'darwin') {buildGhc(false)}} +) -def installPackages(pkgs) { +def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } -def buildGhc(runNofib) { +def buildGhc(boolean runNofib) { + stage('Clean') { + if (false) { + sh 'make distclean' + } + } + stage('Build') { sh 'git submodule update --init --recursive' def speed = 'NORMAL' From git at git.haskell.org Thu May 18 03:36:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 03:36:36 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Run jobs in parallel (77bd4e8) Message-ID: <20170518033636.A20763A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/77bd4e850b9d1427e03f395a9d0fcbd73b04a70f/ghc >--------------------------------------------------------------- commit 77bd4e850b9d1427e03f395a9d0fcbd73b04a70f Author: Ben Gamari Date: Wed May 17 23:34:37 2017 -0400 Run jobs in parallel >--------------------------------------------------------------- 77bd4e850b9d1427e03f395a9d0fcbd73b04a70f Jenkinsfile | 23 ++++++++++++++--------- 1 file changed, 14 insertions(+), 9 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index eada3d5..f2f1423 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,19 +11,24 @@ properties( ]) ]) -//node { buildGhc(runNofib: params.runNofib) } -node(label: 'linux && amd64') { - buildGhc(false) -} -node(label: 'aarch64') { - buildGhc(false) -} +parallel + ( + 'linux x86-64': {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, + 'aarch64': {node(label: 'aarch64') {buildGhc(false)}}, + 'osx': {node(label: 'darwin') {buildGhc(false)}} + ) -def installPackages(pkgs) { +def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } -def buildGhc(runNofib) { +def buildGhc(boolean runNofib) { + stage('Clean') { + if (false) { + sh 'make distclean' + } + } + stage('Build') { sh 'git submodule update --init --recursive' def speed = 'NORMAL' From git at git.haskell.org Thu May 18 03:39:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 03:39:19 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Run jobs in parallel (cb55baa) Message-ID: <20170518033919.5AAF23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/cb55baa12ba7c4b96f8a96c20787de7c8d9519f2/ghc >--------------------------------------------------------------- commit cb55baa12ba7c4b96f8a96c20787de7c8d9519f2 Author: Ben Gamari Date: Wed May 17 23:34:37 2017 -0400 Run jobs in parallel >--------------------------------------------------------------- cb55baa12ba7c4b96f8a96c20787de7c8d9519f2 Jenkinsfile | 23 ++++++++++++++--------- 1 file changed, 14 insertions(+), 9 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index eada3d5..b534ce3 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,19 +11,24 @@ properties( ]) ]) -//node { buildGhc(runNofib: params.runNofib) } -node(label: 'linux && amd64') { - buildGhc(false) -} -node(label: 'aarch64') { - buildGhc(false) -} +parallel + ( + "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, + "aarch64" : {node(label: 'aarch64') {buildGhc(false)}}, + "osx" : {node(label: 'darwin') {buildGhc(false)}} + ) -def installPackages(pkgs) { +def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } -def buildGhc(runNofib) { +def buildGhc(boolean runNofib) { + stage('Clean') { + if (false) { + sh 'make distclean' + } + } + stage('Build') { sh 'git submodule update --init --recursive' def speed = 'NORMAL' From git at git.haskell.org Thu May 18 03:40:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 03:40:52 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Run jobs in parallel (de991cd) Message-ID: <20170518034052.8E1763A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/de991cd32e52c5b3fb591adf52fae40494e24b37/ghc >--------------------------------------------------------------- commit de991cd32e52c5b3fb591adf52fae40494e24b37 Author: Ben Gamari Date: Wed May 17 23:34:37 2017 -0400 Run jobs in parallel >--------------------------------------------------------------- de991cd32e52c5b3fb591adf52fae40494e24b37 Jenkinsfile | 22 +++++++++++++--------- 1 file changed, 13 insertions(+), 9 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index eada3d5..f9debf5 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,19 +11,23 @@ properties( ]) ]) -//node { buildGhc(runNofib: params.runNofib) } -node(label: 'linux && amd64') { - buildGhc(false) -} -node(label: 'aarch64') { - buildGhc(false) -} +parallel ( + "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, + "aarch64" : {node(label: 'aarch64') {buildGhc(false)}}, + "osx" : {node(label: 'darwin') {buildGhc(false)}} +) -def installPackages(pkgs) { +def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } -def buildGhc(runNofib) { +def buildGhc(boolean runNofib) { + stage('Clean') { + if (false) { + sh 'make distclean' + } + } + stage('Build') { sh 'git submodule update --init --recursive' def speed = 'NORMAL' From git at git.haskell.org Thu May 18 03:43:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 03:43:11 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (c8475ce) Message-ID: <20170518034311.86D5F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c8475ce05ea691e9c898ce26880330ba2a17d2a0/ghc >--------------------------------------------------------------- commit c8475ce05ea691e9c898ce26880330ba2a17d2a0 Author: Ben Gamari Date: Wed May 17 23:42:59 2017 -0400 Debug >--------------------------------------------------------------- c8475ce05ea691e9c898ce26880330ba2a17d2a0 Jenkinsfile | 2 ++ 1 file changed, 2 insertions(+) diff --git a/Jenkinsfile b/Jenkinsfile index f9debf5..f66b919 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -29,6 +29,8 @@ def buildGhc(boolean runNofib) { } stage('Build') { + sh 'pwd' + sh 'ls' sh 'git submodule update --init --recursive' def speed = 'NORMAL' if (params.nightly) { From git at git.haskell.org Thu May 18 04:27:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 04:27:29 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (a216c49) Message-ID: <20170518042729.BBC5D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a216c493bb6d344bc7310caa7be5c5920fee08f1/ghc >--------------------------------------------------------------- commit a216c493bb6d344bc7310caa7be5c5920fee08f1 Author: Ben Gamari Date: Wed May 17 23:42:59 2017 -0400 Debug >--------------------------------------------------------------- a216c493bb6d344bc7310caa7be5c5920fee08f1 Jenkinsfile | 12 +++++++++--- 1 file changed, 9 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index f9debf5..e301557 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -12,9 +12,15 @@ properties( ]) parallel ( - "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, - "aarch64" : {node(label: 'aarch64') {buildGhc(false)}}, - "osx" : {node(label: 'darwin') {buildGhc(false)}} + "test" : {node(label: 'linux && aarch64') { + stage('Testing') { + sh 'pwd' + sh 'git clone git://git.haskell.org/ghc' + } + }} + //"linux x86-64" : {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, + //"aarch64" : {node(label: 'linux && aarch64') {buildGhc(false)}}, + //"osx" : {node(label: 'darwin') {buildGhc(false)}} ) def installPackages(String[] pkgs) { From git at git.haskell.org Thu May 18 04:29:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 04:29:09 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (14bf23d) Message-ID: <20170518042909.081EB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/14bf23da13c788511915d4a7f962c27c58e4c5ed/ghc >--------------------------------------------------------------- commit 14bf23da13c788511915d4a7f962c27c58e4c5ed Author: Ben Gamari Date: Wed May 17 23:42:59 2017 -0400 Debug >--------------------------------------------------------------- 14bf23da13c788511915d4a7f962c27c58e4c5ed Jenkinsfile | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index f9debf5..9f49a40 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,9 +11,16 @@ properties( ]) ]) +node(label: 'linux && aarch64') { + stage('Testing') { + sh 'pwd' + sh 'git clone git://git.haskell.org/ghc' + } +} + parallel ( "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, - "aarch64" : {node(label: 'aarch64') {buildGhc(false)}}, + "aarch64" : {node(label: 'linux && aarch64') {buildGhc(false)}}, "osx" : {node(label: 'darwin') {buildGhc(false)}} ) From git at git.haskell.org Thu May 18 04:42:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 04:42:52 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (1b3a26a) Message-ID: <20170518044252.54A533A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/1b3a26a2c4cc619937ec8d5d7468b85401ab4589/ghc >--------------------------------------------------------------- commit 1b3a26a2c4cc619937ec8d5d7468b85401ab4589 Author: Ben Gamari Date: Wed May 17 23:42:59 2017 -0400 Debug >--------------------------------------------------------------- 1b3a26a2c4cc619937ec8d5d7468b85401ab4589 Jenkinsfile | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index f9debf5..89a9dbb 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,9 +11,18 @@ properties( ]) ]) +if (false) { + node(label: 'linux && aarch64') { + stage('Testing') { + sh 'pwd' + sh 'git clone git://git.haskell.org/ghc' + } + } +} + parallel ( "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, - "aarch64" : {node(label: 'aarch64') {buildGhc(false)}}, + "aarch64" : {node(label: 'linux && aarch64') {buildGhc(false)}}, "osx" : {node(label: 'darwin') {buildGhc(false)}} ) From git at git.haskell.org Thu May 18 04:51:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 04:51:55 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (ac52ab2) Message-ID: <20170518045155.79B2F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ac52ab2104976306a92e9b521b2629bb06d0b32e/ghc >--------------------------------------------------------------- commit ac52ab2104976306a92e9b521b2629bb06d0b32e Author: Ben Gamari Date: Wed May 17 23:42:59 2017 -0400 Debug >--------------------------------------------------------------- ac52ab2104976306a92e9b521b2629bb06d0b32e Jenkinsfile | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index f9debf5..16ab84c 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,9 +11,19 @@ properties( ]) ]) +if (true) { + node(label: 'linux && aarch64') { + stage('Testing') { + sh 'pwd' + git 'git://git.haskell.org/ghc' + sh 'ls' + } + } +} + parallel ( "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, - "aarch64" : {node(label: 'aarch64') {buildGhc(false)}}, + "aarch64" : {node(label: 'linux && aarch64') {buildGhc(false)}}, "osx" : {node(label: 'darwin') {buildGhc(false)}} ) From git at git.haskell.org Thu May 18 05:00:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 05:00:53 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Cross (b032796) Message-ID: <20170518050053.BAFB13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/b0327961e3e493b1df012dd9cde05137ef44a586/ghc >--------------------------------------------------------------- commit b0327961e3e493b1df012dd9cde05137ef44a586 Author: Ben Gamari Date: Thu May 18 01:00:42 2017 -0400 Cross >--------------------------------------------------------------- b0327961e3e493b1df012dd9cde05137ef44a586 Jenkinsfile | 13 ++++++++++--- 1 file changed, 10 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 16ab84c..59a6eaa 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,7 +11,7 @@ properties( ]) ]) -if (true) { +if (false) { node(label: 'linux && aarch64') { stage('Testing') { sh 'pwd' @@ -23,6 +23,8 @@ if (true) { parallel ( "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, + "linux x86-64 -> aarch64" : { + node(label: 'linux && amd64') {buildGhc(params.runNofib, 'aarch64-linux-gnu')}}, "aarch64" : {node(label: 'linux && aarch64') {buildGhc(false)}}, "osx" : {node(label: 'darwin') {buildGhc(false)}} ) @@ -31,7 +33,7 @@ def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } -def buildGhc(boolean runNofib) { +def buildGhc(boolean runNofib, String target) { stage('Clean') { if (false) { sh 'make distclean' @@ -52,9 +54,14 @@ def buildGhc(boolean runNofib) { ValidateHpc=NO BUILD_DPH=NO """) + + def target_opt = '' + if (target) { + target_opt = "--target=${target}" + } sh """ ./boot - ./configure --enable-tarballs-autodownload + ./configure --enable-tarballs-autodownload ${target_opt} make -j${env.THREADS} """ } From git at git.haskell.org Thu May 18 05:03:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 05:03:55 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Cross (22f0b20) Message-ID: <20170518050355.DCD033A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/22f0b2013db170e287808c2b79dd4f5921ef369f/ghc >--------------------------------------------------------------- commit 22f0b2013db170e287808c2b79dd4f5921ef369f Author: Ben Gamari Date: Thu May 18 01:00:42 2017 -0400 Cross >--------------------------------------------------------------- 22f0b2013db170e287808c2b79dd4f5921ef369f Jenkinsfile | 13 ++++++++++--- 1 file changed, 10 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 16ab84c..93d0937 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,7 +11,7 @@ properties( ]) ]) -if (true) { +if (false) { node(label: 'linux && aarch64') { stage('Testing') { sh 'pwd' @@ -23,6 +23,8 @@ if (true) { parallel ( "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, + "linux x86-64 -> aarch64" : { + node(label: 'linux && amd64') {buildGhc(params.runNofib, 'aarch64-linux-gnu')}}, "aarch64" : {node(label: 'linux && aarch64') {buildGhc(false)}}, "osx" : {node(label: 'darwin') {buildGhc(false)}} ) @@ -31,7 +33,7 @@ def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } -def buildGhc(boolean runNofib) { +def buildGhc(boolean runNofib, String target_triple) { stage('Clean') { if (false) { sh 'make distclean' @@ -52,9 +54,14 @@ def buildGhc(boolean runNofib) { ValidateHpc=NO BUILD_DPH=NO """) + + def target_opt = '' + if (target_triple) { + target_opt = "--target=${target_triple}" + } sh """ ./boot - ./configure --enable-tarballs-autodownload + ./configure --enable-tarballs-autodownload ${target_opt} make -j${env.THREADS} """ } From git at git.haskell.org Thu May 18 05:04:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 05:04:40 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Cross (adf4945) Message-ID: <20170518050440.D55523A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/adf49457b471e0bf24ca734c8d05e9bc1154f806/ghc >--------------------------------------------------------------- commit adf49457b471e0bf24ca734c8d05e9bc1154f806 Author: Ben Gamari Date: Thu May 18 01:00:42 2017 -0400 Cross >--------------------------------------------------------------- adf49457b471e0bf24ca734c8d05e9bc1154f806 Jenkinsfile | 15 +++++++++++---- 1 file changed, 11 insertions(+), 4 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 16ab84c..1198d02 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,7 +11,7 @@ properties( ]) ]) -if (true) { +if (false) { node(label: 'linux && aarch64') { stage('Testing') { sh 'pwd' @@ -23,15 +23,17 @@ if (true) { parallel ( "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, + "linux x86-64 -> aarch64" : { + node(label: 'linux && amd64') {buildGhc(params.runNofib, 'aarch64-linux-gnu')}}, "aarch64" : {node(label: 'linux && aarch64') {buildGhc(false)}}, - "osx" : {node(label: 'darwin') {buildGhc(false)}} + //"osx" : {node(label: 'darwin') {buildGhc(false)}} ) def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } -def buildGhc(boolean runNofib) { +def buildGhc(boolean runNofib, String target_triple) { stage('Clean') { if (false) { sh 'make distclean' @@ -52,9 +54,14 @@ def buildGhc(boolean runNofib) { ValidateHpc=NO BUILD_DPH=NO """) + + def target_opt = '' + if (target_triple) { + target_opt = "--target=${target_triple}" + } sh """ ./boot - ./configure --enable-tarballs-autodownload + ./configure --enable-tarballs-autodownload ${target_opt} make -j${env.THREADS} """ } From git at git.haskell.org Thu May 18 05:05:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 05:05:51 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Cross (0c54c8c) Message-ID: <20170518050551.D5C2A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0c54c8cfe63aae02489a4e424afbd0ce40160d78/ghc >--------------------------------------------------------------- commit 0c54c8cfe63aae02489a4e424afbd0ce40160d78 Author: Ben Gamari Date: Thu May 18 01:00:42 2017 -0400 Cross >--------------------------------------------------------------- 0c54c8cfe63aae02489a4e424afbd0ce40160d78 Jenkinsfile | 13 ++++++++++--- 1 file changed, 10 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 16ab84c..bb8a626 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -23,15 +23,17 @@ if (true) { parallel ( "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, + "linux x86-64 -> aarch64" : { + node(label: 'linux && amd64') {buildGhc(params.runNofib, 'aarch64-linux-gnu')}}, "aarch64" : {node(label: 'linux && aarch64') {buildGhc(false)}}, - "osx" : {node(label: 'darwin') {buildGhc(false)}} + //"osx" : {node(label: 'darwin') {buildGhc(false)}} ) def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } -def buildGhc(boolean runNofib) { +def buildGhc(boolean runNofib, String target_triple) { stage('Clean') { if (false) { sh 'make distclean' @@ -52,9 +54,14 @@ def buildGhc(boolean runNofib) { ValidateHpc=NO BUILD_DPH=NO """) + + def target_opt = '' + if (target_triple) { + target_opt = "--target=${target_triple}" + } sh """ ./boot - ./configure --enable-tarballs-autodownload + ./configure --enable-tarballs-autodownload ${target_opt} make -j${env.THREADS} """ } From git at git.haskell.org Thu May 18 05:11:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 05:11:30 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Cross (bdf8c6e) Message-ID: <20170518051130.4B7ED3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/bdf8c6e01d877f6f5ba1607305b2b8d2198e5f77/ghc >--------------------------------------------------------------- commit bdf8c6e01d877f6f5ba1607305b2b8d2198e5f77 Author: Ben Gamari Date: Thu May 18 01:00:42 2017 -0400 Cross >--------------------------------------------------------------- bdf8c6e01d877f6f5ba1607305b2b8d2198e5f77 Jenkinsfile | 49 ++++++++++++++++++++++++++++++++----------------- 1 file changed, 32 insertions(+), 17 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 16ab84c..409d9ec 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -23,15 +23,17 @@ if (true) { parallel ( "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, + "linux x86-64 -> aarch64" : { + node(label: 'linux && amd64') {buildGhc(params.runNofib, 'aarch64-linux-gnu')}}, "aarch64" : {node(label: 'linux && aarch64') {buildGhc(false)}}, - "osx" : {node(label: 'darwin') {buildGhc(false)}} + //"osx" : {node(label: 'darwin') {buildGhc(false)}} ) def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } -def buildGhc(boolean runNofib) { +def buildGhc(boolean runNofib, String cross_target) { stage('Clean') { if (false) { sh 'make distclean' @@ -44,23 +46,34 @@ def buildGhc(boolean runNofib) { if (params.nightly) { speed = 'SLOW' } - writeFile( - file: 'mk/build.mk', - text: """ - Validating=YES - ValidateSpeed=${speed} - ValidateHpc=NO - BUILD_DPH=NO - """) + build_mk = """ + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + """ + if (cross_target) { + build_mk += """ + HADDOCK_DOCS=NO + SPHINX_HTML_DOCS=NO + SPHINX_PDF_DOCS=NO + """ + } + writeFile(file: 'mk/build.mk', text: build_mk) + + def target_opt = '' + if (cross_target) { + target_opt = "--target=${cross_target}" + } sh """ ./boot - ./configure --enable-tarballs-autodownload + ./configure --enable-tarballs-autodownload ${target_opt} make -j${env.THREADS} """ } stage('Install testsuite dependencies') { - if (params.nightly) { + if (params.nightly && !cross_target) { def pkgs = ['mtl', 'parallel', 'parsec', 'primitive', 'QuickCheck', 'random', 'regex-compat', 'syb', 'stm', 'utf8-string', 'vector'] @@ -69,15 +82,17 @@ def buildGhc(boolean runNofib) { } stage('Run testsuite') { - def target = 'test' - if (params.nightly) { - target = 'slowtest' + if (!cross_target) { + def target = 'test' + if (params.nightly) { + target = 'slowtest' + } + sh "make THREADS=${env.THREADS} ${target}" } - sh "make THREADS=${env.THREADS} ${target}" } stage('Run nofib') { - if (runNofib) { + if (runNofib && !cross_target) { installPkgs(['regex-compat']) sh """ cd nofib From git at git.haskell.org Thu May 18 05:20:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 05:20:08 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Checkout (f6973c7) Message-ID: <20170518052008.8E5063A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/f6973c769a032917b045b96255a774ebaa186c15/ghc >--------------------------------------------------------------- commit f6973c769a032917b045b96255a774ebaa186c15 Author: Ben Gamari Date: Thu May 18 01:19:52 2017 -0400 Checkout >--------------------------------------------------------------- f6973c769a032917b045b96255a774ebaa186c15 Jenkinsfile | 1 + 1 file changed, 1 insertion(+) diff --git a/Jenkinsfile b/Jenkinsfile index 409d9ec..a584aff 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -35,6 +35,7 @@ def installPackages(String[] pkgs) { def buildGhc(boolean runNofib, String cross_target) { stage('Clean') { + checkout(recursiveSubmodules: true, clean: true) if (false) { sh 'make distclean' } From git at git.haskell.org Thu May 18 05:32:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 05:32:11 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Checkout (54dc828) Message-ID: <20170518053211.0E1873A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/54dc828496e2f511333c6c7fd59eaf13db7bfd89/ghc >--------------------------------------------------------------- commit 54dc828496e2f511333c6c7fd59eaf13db7bfd89 Author: Ben Gamari Date: Thu May 18 01:19:52 2017 -0400 Checkout >--------------------------------------------------------------- 54dc828496e2f511333c6c7fd59eaf13db7bfd89 Jenkinsfile | 1 + 1 file changed, 1 insertion(+) diff --git a/Jenkinsfile b/Jenkinsfile index 409d9ec..b9fa972 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -35,6 +35,7 @@ def installPackages(String[] pkgs) { def buildGhc(boolean runNofib, String cross_target) { stage('Clean') { + checkout scm if (false) { sh 'make distclean' } From git at git.haskell.org Thu May 18 05:39:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 05:39:08 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: More things (d6148e2) Message-ID: <20170518053908.C1C7E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d6148e2efc8b69a334b68b1cf58394c9093926a9/ghc >--------------------------------------------------------------- commit d6148e2efc8b69a334b68b1cf58394c9093926a9 Author: Ben Gamari Date: Thu May 18 01:38:55 2017 -0400 More things >--------------------------------------------------------------- d6148e2efc8b69a334b68b1cf58394c9093926a9 Jenkinsfile | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index b9fa972..04d8d84 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -33,7 +33,7 @@ def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } -def buildGhc(boolean runNofib, String cross_target) { +def buildGhc(boolean runNofib, String cross_target=null) { stage('Clean') { checkout scm if (false) { @@ -55,9 +55,10 @@ def buildGhc(boolean runNofib, String cross_target) { """ if (cross_target) { build_mk += """ + # Cross compiling HADDOCK_DOCS=NO - SPHINX_HTML_DOCS=NO - SPHINX_PDF_DOCS=NO + BUILD_SPHINX_HTML=NO + BUILD_SPHINX_PDF=NO """ } writeFile(file: 'mk/build.mk', text: build_mk) From git at git.haskell.org Thu May 18 06:15:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 06:15:04 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Kill debugging (72e3ea6) Message-ID: <20170518061504.E00E03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/72e3ea6e573f1720f34873d4e45120392b69a89d/ghc >--------------------------------------------------------------- commit 72e3ea6e573f1720f34873d4e45120392b69a89d Author: Ben Gamari Date: Thu May 18 01:39:32 2017 -0400 Kill debugging >--------------------------------------------------------------- 72e3ea6e573f1720f34873d4e45120392b69a89d Jenkinsfile | 10 ---------- 1 file changed, 10 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 04d8d84..d759a03 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,16 +11,6 @@ properties( ]) ]) -if (true) { - node(label: 'linux && aarch64') { - stage('Testing') { - sh 'pwd' - git 'git://git.haskell.org/ghc' - sh 'ls' - } - } -} - parallel ( "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, "linux x86-64 -> aarch64" : { From git at git.haskell.org Thu May 18 06:15:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 06:15:07 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Unregisterised (a5b1d5d) Message-ID: <20170518061507.99D4E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a5b1d5dd7a3cfe27bc65ed82cddd842b3323903d/ghc >--------------------------------------------------------------- commit a5b1d5dd7a3cfe27bc65ed82cddd842b3323903d Author: Ben Gamari Date: Thu May 18 01:55:35 2017 -0400 Unregisterised >--------------------------------------------------------------- a5b1d5dd7a3cfe27bc65ed82cddd842b3323903d Jenkinsfile | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index d759a03..ecaf027 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -23,7 +23,7 @@ def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } -def buildGhc(boolean runNofib, String cross_target=null) { +def buildGhc(boolean runNofib, String cross_target=null, boolean unreg=false) { stage('Clean') { checkout scm if (false) { @@ -53,9 +53,12 @@ def buildGhc(boolean runNofib, String cross_target=null) { } writeFile(file: 'mk/build.mk', text: build_mk) - def target_opt = '' + def configure_opts = '--enable-tarballs-autodownload' if (cross_target) { - target_opt = "--target=${cross_target}" + configure_opts += "--target=${cross_target}" + } + if (unreg) { + configure_opts += "--enable-unregisterised" } sh """ ./boot From git at git.haskell.org Thu May 18 06:15:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 06:15:10 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: windows (9bb2e7c) Message-ID: <20170518061510.548A43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9bb2e7c8344cec3712e6ad58a923ff652bceb4ea/ghc >--------------------------------------------------------------- commit 9bb2e7c8344cec3712e6ad58a923ff652bceb4ea Author: Ben Gamari Date: Thu May 18 01:55:46 2017 -0400 windows >--------------------------------------------------------------- 9bb2e7c8344cec3712e6ad58a923ff652bceb4ea Jenkinsfile | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index ecaf027..466a726 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -12,11 +12,13 @@ properties( ]) parallel ( - "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, + "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, + "linux x86-64 unreg" : {node(label: 'linux && amd64') {buildGhc(false, null, false)}}, "linux x86-64 -> aarch64" : { - node(label: 'linux && amd64') {buildGhc(params.runNofib, 'aarch64-linux-gnu')}}, - "aarch64" : {node(label: 'linux && aarch64') {buildGhc(false)}}, - //"osx" : {node(label: 'darwin') {buildGhc(false)}} + node(label: 'linux && amd64') {buildGhc(params.runNofib, 'aarch64-linux-gnu')}}, + "aarch64" : {node(label: 'linux && aarch64') {buildGhc(false)}}, + "windows 64" : {node(label: 'windows && amd64') {buildGhc(false)}}, + //"osx" : {node(label: 'darwin') {buildGhc(false)}} ) def installPackages(String[] pkgs) { From git at git.haskell.org Thu May 18 06:15:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 06:15:13 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring, add Windows, fix cross (08f3b7d) Message-ID: <20170518061513.0DA8D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/08f3b7de8e3ee3b1e26bf2a4ea71bc390a9ba8b7/ghc >--------------------------------------------------------------- commit 08f3b7de8e3ee3b1e26bf2a4ea71bc390a9ba8b7 Author: Ben Gamari Date: Thu May 18 02:14:40 2017 -0400 Refactoring, add Windows, fix cross >--------------------------------------------------------------- 08f3b7de8e3ee3b1e26bf2a4ea71bc390a9ba8b7 Jenkinsfile | 37 +++++++++++++++++++++---------------- 1 file changed, 21 insertions(+), 16 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 466a726..8b6e1c0 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -13,11 +13,12 @@ properties( parallel ( "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, - "linux x86-64 unreg" : {node(label: 'linux && amd64') {buildGhc(false, null, false)}}, + "linux x86-64 unreg" : {node(label: 'linux && amd64') {buildGhc(unreg: true)}}, "linux x86-64 -> aarch64" : { - node(label: 'linux && amd64') {buildGhc(params.runNofib, 'aarch64-linux-gnu')}}, - "aarch64" : {node(label: 'linux && aarch64') {buildGhc(false)}}, - "windows 64" : {node(label: 'windows && amd64') {buildGhc(false)}}, + node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib, crossTarget: 'aarch64-linux-gnu')}}, + "aarch64" : {node(label: 'linux && aarch64') {buildGhc()}}, + "windows 64" : {node(label: 'windows && amd64') {buildGhc(msys: 64)}}, + "windows 32" : {node(label: 'windows && amd64') {buildGhc(msys: 32)}}, //"osx" : {node(label: 'darwin') {buildGhc(false)}} ) @@ -25,12 +26,14 @@ def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } -def buildGhc(boolean runNofib, String cross_target=null, boolean unreg=false) { - stage('Clean') { +def buildGhc(params) { + boolean runNoFib = params?.runNofib ?: false + String crossTarget = params?.crossTarget + boolean unreg = params?.unreg ?: false + String msys = params?.msys; + + stage('Checkout') { checkout scm - if (false) { - sh 'make distclean' - } } stage('Build') { @@ -45,32 +48,34 @@ def buildGhc(boolean runNofib, String cross_target=null, boolean unreg=false) { ValidateHpc=NO BUILD_DPH=NO """ - if (cross_target) { + if (crossTarget) { build_mk += """ # Cross compiling HADDOCK_DOCS=NO BUILD_SPHINX_HTML=NO BUILD_SPHINX_PDF=NO + INTEGER_LIBRARY=integer-simple + WITH_TERMINFO=NO """ } writeFile(file: 'mk/build.mk', text: build_mk) def configure_opts = '--enable-tarballs-autodownload' - if (cross_target) { - configure_opts += "--target=${cross_target}" + if (crossTarget) { + configure_opts += "--target=${crossTarget}" } if (unreg) { configure_opts += "--enable-unregisterised" } sh """ ./boot - ./configure --enable-tarballs-autodownload ${target_opt} + ./configure ${configure_opts} make -j${env.THREADS} """ } stage('Install testsuite dependencies') { - if (params.nightly && !cross_target) { + if (params.nightly && !crossTarget) { def pkgs = ['mtl', 'parallel', 'parsec', 'primitive', 'QuickCheck', 'random', 'regex-compat', 'syb', 'stm', 'utf8-string', 'vector'] @@ -79,7 +84,7 @@ def buildGhc(boolean runNofib, String cross_target=null, boolean unreg=false) { } stage('Run testsuite') { - if (!cross_target) { + if (!crossTarget) { def target = 'test' if (params.nightly) { target = 'slowtest' @@ -89,7 +94,7 @@ def buildGhc(boolean runNofib, String cross_target=null, boolean unreg=false) { } stage('Run nofib') { - if (runNofib && !cross_target) { + if (runNofib && !crossTarget) { installPkgs(['regex-compat']) sh """ cd nofib From git at git.haskell.org Thu May 18 06:18:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 06:18:52 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring, add Windows, fix cross (50dbdb4) Message-ID: <20170518061852.B951B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/50dbdb454518941abfad786234da72ba49fd77b1/ghc >--------------------------------------------------------------- commit 50dbdb454518941abfad786234da72ba49fd77b1 Author: Ben Gamari Date: Thu May 18 02:14:40 2017 -0400 Refactoring, add Windows, fix cross >--------------------------------------------------------------- 50dbdb454518941abfad786234da72ba49fd77b1 Jenkinsfile | 41 +++++++++++++++++++++++------------------ 1 file changed, 23 insertions(+), 18 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 466a726..7556b50 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -12,25 +12,28 @@ properties( ]) parallel ( - "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(params.runNofib)}}, - "linux x86-64 unreg" : {node(label: 'linux && amd64') {buildGhc(false, null, false)}}, + "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib)}}, + "linux x86-64 unreg" : {node(label: 'linux && amd64') {buildGhc(unreg: true)}}, "linux x86-64 -> aarch64" : { - node(label: 'linux && amd64') {buildGhc(params.runNofib, 'aarch64-linux-gnu')}}, - "aarch64" : {node(label: 'linux && aarch64') {buildGhc(false)}}, - "windows 64" : {node(label: 'windows && amd64') {buildGhc(false)}}, - //"osx" : {node(label: 'darwin') {buildGhc(false)}} + node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib, crossTarget: 'aarch64-linux-gnu')}}, + "aarch64" : {node(label: 'linux && aarch64') {buildGhc(runNoFib: false)}}, + "windows 64" : {node(label: 'windows && amd64') {buildGhc(msys: 64)}}, + "windows 32" : {node(label: 'windows && amd64') {buildGhc(msys: 32)}}, + //"osx" : {node(label: 'darwin') {buildGhc(runNoFib: params.runNoFib)}} ) def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } -def buildGhc(boolean runNofib, String cross_target=null, boolean unreg=false) { - stage('Clean') { +def buildGhc(params) { + boolean runNoFib = params?.runNofib ?: false + String crossTarget = params?.crossTarget + boolean unreg = params?.unreg ?: false + String msys = params?.msys; + + stage('Checkout') { checkout scm - if (false) { - sh 'make distclean' - } } stage('Build') { @@ -45,32 +48,34 @@ def buildGhc(boolean runNofib, String cross_target=null, boolean unreg=false) { ValidateHpc=NO BUILD_DPH=NO """ - if (cross_target) { + if (crossTarget) { build_mk += """ # Cross compiling HADDOCK_DOCS=NO BUILD_SPHINX_HTML=NO BUILD_SPHINX_PDF=NO + INTEGER_LIBRARY=integer-simple + WITH_TERMINFO=NO """ } writeFile(file: 'mk/build.mk', text: build_mk) def configure_opts = '--enable-tarballs-autodownload' - if (cross_target) { - configure_opts += "--target=${cross_target}" + if (crossTarget) { + configure_opts += "--target=${crossTarget}" } if (unreg) { configure_opts += "--enable-unregisterised" } sh """ ./boot - ./configure --enable-tarballs-autodownload ${target_opt} + ./configure ${configure_opts} make -j${env.THREADS} """ } stage('Install testsuite dependencies') { - if (params.nightly && !cross_target) { + if (params.nightly && !crossTarget) { def pkgs = ['mtl', 'parallel', 'parsec', 'primitive', 'QuickCheck', 'random', 'regex-compat', 'syb', 'stm', 'utf8-string', 'vector'] @@ -79,7 +84,7 @@ def buildGhc(boolean runNofib, String cross_target=null, boolean unreg=false) { } stage('Run testsuite') { - if (!cross_target) { + if (!crossTarget) { def target = 'test' if (params.nightly) { target = 'slowtest' @@ -89,7 +94,7 @@ def buildGhc(boolean runNofib, String cross_target=null, boolean unreg=false) { } stage('Run nofib') { - if (runNofib && !cross_target) { + if (runNofib && !crossTarget) { installPkgs(['regex-compat']) sh """ cd nofib From git at git.haskell.org Thu May 18 06:56:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 06:56:27 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (a7de8a2) Message-ID: <20170518065627.9823B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a7de8a2535aa775dae1eb423c1b8674ea924a262/ghc >--------------------------------------------------------------- commit a7de8a2535aa775dae1eb423c1b8674ea924a262 Author: Ben Gamari Date: Thu May 18 02:56:06 2017 -0400 Debug >--------------------------------------------------------------- a7de8a2535aa775dae1eb423c1b8674ea924a262 Jenkinsfile | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 7556b50..aff2240 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -34,10 +34,12 @@ def buildGhc(params) { stage('Checkout') { checkout scm + sh """git submodule update --init --recursive + echo hello + """ } stage('Build') { - sh 'git submodule update --init --recursive' def speed = 'NORMAL' if (params.nightly) { speed = 'SLOW' From git at git.haskell.org Thu May 18 06:58:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 06:58:17 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Reformat (4e1ce6d) Message-ID: <20170518065817.899FA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/4e1ce6db098d0a847289e53db96e9b2a084c5610/ghc >--------------------------------------------------------------- commit 4e1ce6db098d0a847289e53db96e9b2a084c5610 Author: Ben Gamari Date: Thu May 18 02:58:05 2017 -0400 Reformat >--------------------------------------------------------------- 4e1ce6db098d0a847289e53db96e9b2a084c5610 Jenkinsfile | 25 +++++++++++++++++++------ 1 file changed, 19 insertions(+), 6 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index aff2240..9af2814 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -12,13 +12,26 @@ properties( ]) parallel ( - "linux x86-64" : {node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib)}}, - "linux x86-64 unreg" : {node(label: 'linux && amd64') {buildGhc(unreg: true)}}, + "linux x86-64" : { + node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib)} + }, + "linux x86-64 -> aarch64 unreg" : { + node(label: 'linux && amd64') {buildGhc(crossTarget: 'aarch64-linux-gnu', unreg: true)} + }, "linux x86-64 -> aarch64" : { - node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib, crossTarget: 'aarch64-linux-gnu')}}, - "aarch64" : {node(label: 'linux && aarch64') {buildGhc(runNoFib: false)}}, - "windows 64" : {node(label: 'windows && amd64') {buildGhc(msys: 64)}}, - "windows 32" : {node(label: 'windows && amd64') {buildGhc(msys: 32)}}, + node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib, crossTarget: 'aarch64-linux-gnu')} + }, + "aarch64" : { + node(label: 'linux && aarch64') {buildGhc(runNoFib: false)} + }, + // Requires cygpath plugin? + // Make + "windows 64" : { + node(label: 'windows && amd64') {buildGhc(msys: 64)} + }, + "windows 32" : { + node(label: 'windows && amd64') {buildGhc(msys: 32)} + }, //"osx" : {node(label: 'darwin') {buildGhc(runNoFib: params.runNoFib)}} ) From git at git.haskell.org Thu May 18 06:59:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 06:59:51 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (e096bbd) Message-ID: <20170518065951.B16FE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/e096bbddccefdf69e138afc615ae1e12ffbf6d2e/ghc >--------------------------------------------------------------- commit e096bbddccefdf69e138afc615ae1e12ffbf6d2e Author: Ben Gamari Date: Thu May 18 02:59:40 2017 -0400 Debug >--------------------------------------------------------------- e096bbddccefdf69e138afc615ae1e12ffbf6d2e Jenkinsfile | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 9af2814..0bd3c7b 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -47,9 +47,11 @@ def buildGhc(params) { stage('Checkout') { checkout scm - sh """git submodule update --init --recursive - echo hello - """ + if (msys) { + bat "git submodule update --init --recursive" + } else { + sh "git submodule update --init --recursive" + } } stage('Build') { From git at git.haskell.org Thu May 18 12:44:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 May 2017 12:44:32 +0000 (UTC) Subject: [commit: ghc] master: Insert missing newline (7b52525) Message-ID: <20170518124432.939E43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7b52525ecb2a09b21e7e5393f45a72ed1dfa3bc8/ghc >--------------------------------------------------------------- commit 7b52525ecb2a09b21e7e5393f45a72ed1dfa3bc8 Author: Frederik Hanghøj Iversen Date: Thu May 18 14:26:10 2017 +0200 Insert missing newline >--------------------------------------------------------------- 7b52525ecb2a09b21e7e5393f45a72ed1dfa3bc8 libraries/base/GHC/TopHandler.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/GHC/TopHandler.hs b/libraries/base/GHC/TopHandler.hs index 1b1e065..65ac1a6 100644 --- a/libraries/base/GHC/TopHandler.hs +++ b/libraries/base/GHC/TopHandler.hs @@ -208,7 +208,7 @@ disasterHandler exit _ = errorBelch fmt msg >> exit 1 where msgStr = - "encountered an exception while trying to report an exception." ++ + "encountered an exception while trying to report an exception.\n" ++ "One possible reason for this is that we failed while trying to " ++ "encode an error message. Check that your locale is configured " ++ "properly." From git at git.haskell.org Fri May 19 10:11:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 May 2017 10:11:59 +0000 (UTC) Subject: [commit: ghc] master: Ensure that insolubles are fully rewritten (433b80d) Message-ID: <20170519101159.B6D153A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/433b80dec1cfef787fc1327a9eada1791b11c12e/ghc >--------------------------------------------------------------- commit 433b80dec1cfef787fc1327a9eada1791b11c12e Author: Simon Peyton Jones Date: Fri May 19 10:50:35 2017 +0100 Ensure that insolubles are fully rewritten I was alerted to this by Trac #12468 and #11325. We were treating insolubles (and "hole" constraints are treated as insoluble) inconsistently. In some places we were carefully rewriting them e.g. Note [Make sure that insolubles are fully rewritten] in TcCanonical. But in TcSimplify we weren't feeding them into the solver. As a result, "hole" constraints were not being rewritten, which some users found confusing, and I think rightly so. This patch also fixes a bug in TcSMonad.emitInsoluble, in which two different "hole" constriants could be treated (bogusly) as duplicates, thereby losing one. >--------------------------------------------------------------- 433b80dec1cfef787fc1327a9eada1791b11c12e compiler/typecheck/TcCanonical.hs | 2 +- compiler/typecheck/TcRnTypes.hs | 15 +++++---- compiler/typecheck/TcSMonad.hs | 38 +++++++++++++++------- compiler/typecheck/TcSimplify.hs | 28 ++++++++++------ testsuite/tests/gadt/T12468.hs | 9 +++++ testsuite/tests/gadt/T12468.stderr | 6 ++++ testsuite/tests/gadt/all.T | 1 + .../should_compile/hole_constraints.stderr | 4 +-- 8 files changed, 73 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 433b80dec1cfef787fc1327a9eada1791b11c12e From git at git.haskell.org Fri May 19 11:21:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 May 2017 11:21:25 +0000 (UTC) Subject: [commit: ghc] master: Fix Haddock markup (c039624) Message-ID: <20170519112125.B24E33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c039624a83f3eacf03dbe41c3f6e3362d7ef6666/ghc >--------------------------------------------------------------- commit c039624a83f3eacf03dbe41c3f6e3362d7ef6666 Author: Alexey Vagarenko Date: Fri May 19 02:49:18 2017 +0500 Fix Haddock markup >--------------------------------------------------------------- c039624a83f3eacf03dbe41c3f6e3362d7ef6666 libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 8be48aa..31e5ccd 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -1538,7 +1538,7 @@ data Exp | ConE Name -- ^ @data T1 = C1 t1 t2; p = {C1} e1 e2 @ | LitE Lit -- ^ @{ 5 or \'c\'}@ | AppE Exp Exp -- ^ @{ f x }@ - | AppTypeE Exp Type -- ^ @{ f \@Int } + | AppTypeE Exp Type -- ^ @{ f \@Int }@ | InfixE (Maybe Exp) Exp (Maybe Exp) -- ^ @{x + y} or {(x+)} or {(+ x)} or {(+)}@ From git at git.haskell.org Fri May 19 11:24:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 May 2017 11:24:18 +0000 (UTC) Subject: [commit: ghc] master: Comments and white space only (875159c) Message-ID: <20170519112418.8AE073A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/875159cc89d7d7120395e026330397a620531c25/ghc >--------------------------------------------------------------- commit 875159cc89d7d7120395e026330397a620531c25 Author: Simon Peyton Jones Date: Fri May 19 11:55:38 2017 +0100 Comments and white space only >--------------------------------------------------------------- 875159cc89d7d7120395e026330397a620531c25 compiler/iface/MkIface.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/compiler/iface/MkIface.hs b/compiler/iface/MkIface.hs index 4968c29..dec7215 100644 --- a/compiler/iface/MkIface.hs +++ b/compiler/iface/MkIface.hs @@ -476,10 +476,9 @@ addFingerprints hsc_env mb_old_fingerprint iface0 new_decls extendOccEnvList env [ (b,n) | b <- ifaceDeclImplicitBndrs d ] where n = getOccName d - -- strongly-connected groups of declarations, in dependency order + -- Strongly-connected groups of declarations, in dependency order groups :: [SCC IfaceDeclABI] - groups = - stronglyConnCompFromEdgedVerticesUniq edges + groups = stronglyConnCompFromEdgedVerticesUniq edges global_hash_fn = mkHashFun hsc_env eps From git at git.haskell.org Fri May 19 11:24:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 May 2017 11:24:21 +0000 (UTC) Subject: [commit: ghc] master: Refactor freeNamesIfDecl (d06cb96) Message-ID: <20170519112421.4A4633A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d06cb9633ec887f7575007dec66dec3a5736dbeb/ghc >--------------------------------------------------------------- commit d06cb9633ec887f7575007dec66dec3a5736dbeb Author: Simon Peyton Jones Date: Fri May 19 11:57:21 2017 +0100 Refactor freeNamesIfDecl This just switches to using pattern matching rather than field selectors, which I generally prefer. No change in behaviour. >--------------------------------------------------------------- d06cb9633ec887f7575007dec66dec3a5736dbeb compiler/iface/IfaceSyn.hs | 112 +++++++++++++++++++++++++++------------------ 1 file changed, 68 insertions(+), 44 deletions(-) diff --git a/compiler/iface/IfaceSyn.hs b/compiler/iface/IfaceSyn.hs index aadb7b5..d5ca24e 100644 --- a/compiler/iface/IfaceSyn.hs +++ b/compiler/iface/IfaceSyn.hs @@ -1261,44 +1261,65 @@ fingerprinting the instance, so DFuns are not dependencies. -} freeNamesIfDecl :: IfaceDecl -> NameSet -freeNamesIfDecl (IfaceId _s t d i) = - freeNamesIfType t &&& - freeNamesIfIdInfo i &&& - freeNamesIfIdDetails d -freeNamesIfDecl d at IfaceData{} = - freeNamesIfTyVarBndrs (ifBinders d) &&& - freeNamesIfType (ifResKind d) &&& - freeNamesIfaceTyConParent (ifParent d) &&& - freeNamesIfContext (ifCtxt d) &&& - freeNamesIfConDecls (ifCons d) -freeNamesIfDecl d at IfaceSynonym{} = - freeNamesIfType (ifSynRhs d) &&& - freeNamesIfTyVarBndrs (ifBinders d) &&& - freeNamesIfKind (ifResKind d) -freeNamesIfDecl d at IfaceFamily{} = - freeNamesIfFamFlav (ifFamFlav d) &&& - freeNamesIfTyVarBndrs (ifBinders d) &&& - freeNamesIfKind (ifResKind d) -freeNamesIfDecl d at IfaceClass{ ifBody = IfAbstractClass } = - freeNamesIfTyVarBndrs (ifBinders d) -freeNamesIfDecl d at IfaceClass{ ifBody = d'@IfConcreteClass{} } = - freeNamesIfTyVarBndrs (ifBinders d) &&& - freeNamesIfContext (ifClassCtxt d') &&& - fnList freeNamesIfAT (ifATs d') &&& - fnList freeNamesIfClsSig (ifSigs d') -freeNamesIfDecl d at IfaceAxiom{} = - freeNamesIfTc (ifTyCon d) &&& - fnList freeNamesIfAxBranch (ifAxBranches d) -freeNamesIfDecl d at IfacePatSyn{} = - unitNameSet (fst (ifPatMatcher d)) &&& - maybe emptyNameSet (unitNameSet . fst) (ifPatBuilder d) &&& - freeNamesIfTyVarBndrs (ifPatUnivBndrs d) &&& - freeNamesIfTyVarBndrs (ifPatExBndrs d) &&& - freeNamesIfContext (ifPatProvCtxt d) &&& - freeNamesIfContext (ifPatReqCtxt d) &&& - fnList freeNamesIfType (ifPatArgs d) &&& - freeNamesIfType (ifPatTy d) &&& - mkNameSet (map flSelector (ifFieldLabels d)) +freeNamesIfDecl (IfaceId { ifType = t, ifIdDetails = d, ifIdInfo = i}) + = freeNamesIfType t &&& + freeNamesIfIdInfo i &&& + freeNamesIfIdDetails d + +freeNamesIfDecl (IfaceData { ifBinders = bndrs, ifResKind = res_k + , ifParent = p, ifCtxt = ctxt, ifCons = cons }) + = freeNamesIfTyVarBndrs bndrs &&& + freeNamesIfType res_k &&& + freeNamesIfaceTyConParent p &&& + freeNamesIfContext ctxt &&& + freeNamesIfConDecls cons + +freeNamesIfDecl (IfaceSynonym { ifBinders = bndrs, ifResKind = res_k + , ifSynRhs = rhs }) + = freeNamesIfTyVarBndrs bndrs &&& + freeNamesIfKind res_k &&& + freeNamesIfType rhs + +freeNamesIfDecl (IfaceFamily { ifBinders = bndrs, ifResKind = res_k + , ifFamFlav = flav }) + = freeNamesIfTyVarBndrs bndrs &&& + freeNamesIfKind res_k &&& + freeNamesIfFamFlav flav + +freeNamesIfDecl (IfaceClass{ ifBinders = bndrs, ifBody = cls_body }) + = freeNamesIfTyVarBndrs bndrs &&& + freeNamesIfClassBody cls_body + +freeNamesIfDecl (IfaceAxiom { ifTyCon = tc, ifAxBranches = branches }) + = freeNamesIfTc tc &&& + fnList freeNamesIfAxBranch branches + +freeNamesIfDecl (IfacePatSyn { ifPatMatcher = (matcher, _) + , ifPatBuilder = mb_builder + , ifPatUnivBndrs = univ_bndrs + , ifPatExBndrs = ex_bndrs + , ifPatProvCtxt = prov_ctxt + , ifPatReqCtxt = req_ctxt + , ifPatArgs = args + , ifPatTy = pat_ty + , ifFieldLabels = lbls }) + = unitNameSet matcher &&& + maybe emptyNameSet (unitNameSet . fst) mb_builder &&& + freeNamesIfTyVarBndrs univ_bndrs &&& + freeNamesIfTyVarBndrs ex_bndrs &&& + freeNamesIfContext prov_ctxt &&& + freeNamesIfContext req_ctxt &&& + fnList freeNamesIfType args &&& + freeNamesIfType pat_ty &&& + mkNameSet (map flSelector lbls) + +freeNamesIfClassBody :: IfaceClassBody -> NameSet +freeNamesIfClassBody IfAbstractClass + = emptyNameSet +freeNamesIfClassBody (IfConcreteClass{ ifClassCtxt = ctxt, ifATs = ats, ifSigs = sigs }) + = freeNamesIfContext ctxt &&& + fnList freeNamesIfAT ats &&& + fnList freeNamesIfClsSig sigs freeNamesIfAxBranch :: IfaceAxBranch -> NameSet freeNamesIfAxBranch (IfaceAxBranch { ifaxbTyVars = tyvars @@ -1348,12 +1369,15 @@ freeNamesIfConDecls (IfNewTyCon c) = freeNamesIfConDecl c freeNamesIfConDecls _ = emptyNameSet freeNamesIfConDecl :: IfaceConDecl -> NameSet -freeNamesIfConDecl c - = freeNamesIfTyVarBndrs (ifConExTvs c) &&& - freeNamesIfContext (ifConCtxt c) &&& - fnList freeNamesIfType (ifConArgTys c) &&& - mkNameSet (map flSelector (ifConFields c)) &&& - fnList freeNamesIfType (map snd (ifConEqSpec c)) -- equality constraints +freeNamesIfConDecl (IfCon { ifConExTvs = ex_tvs, ifConCtxt = ctxt + , ifConArgTys = arg_tys + , ifConFields = flds + , ifConEqSpec = eq_spec }) + = freeNamesIfTyVarBndrs ex_tvs &&& + freeNamesIfContext ctxt &&& + fnList freeNamesIfType arg_tys &&& + mkNameSet (map flSelector flds) &&& + fnList freeNamesIfType (map snd eq_spec) -- equality constraints freeNamesIfKind :: IfaceType -> NameSet freeNamesIfKind = freeNamesIfType From git at git.haskell.org Fri May 19 11:24:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 May 2017 11:24:15 +0000 (UTC) Subject: [commit: ghc] master: Account for IfUnpackCo in freeNamesIfDecl (8fe37a0) Message-ID: <20170519112415.CCDD53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8fe37a0222517c3af5ffbb793fa738ad7f3eac3d/ghc >--------------------------------------------------------------- commit 8fe37a0222517c3af5ffbb793fa738ad7f3eac3d Author: Simon Peyton Jones Date: Fri May 19 12:00:26 2017 +0100 Account for IfUnpackCo in freeNamesIfDecl We were simply failing to recognise all the free variables of an IfaceDecl, notably the ones in the coercion of an IfUnpackCo. Result: the dependency analysis got messed up, so that fingerprint calculation went wrong. Trac #13695 showed it up. A test case is tricky but the fix is a solid one. >--------------------------------------------------------------- 8fe37a0222517c3af5ffbb793fa738ad7f3eac3d compiler/iface/IfaceSyn.hs | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/compiler/iface/IfaceSyn.hs b/compiler/iface/IfaceSyn.hs index d5ca24e..338397d 100644 --- a/compiler/iface/IfaceSyn.hs +++ b/compiler/iface/IfaceSyn.hs @@ -1372,12 +1372,18 @@ freeNamesIfConDecl :: IfaceConDecl -> NameSet freeNamesIfConDecl (IfCon { ifConExTvs = ex_tvs, ifConCtxt = ctxt , ifConArgTys = arg_tys , ifConFields = flds - , ifConEqSpec = eq_spec }) + , ifConEqSpec = eq_spec + , ifConStricts = bangs }) = freeNamesIfTyVarBndrs ex_tvs &&& freeNamesIfContext ctxt &&& fnList freeNamesIfType arg_tys &&& mkNameSet (map flSelector flds) &&& - fnList freeNamesIfType (map snd eq_spec) -- equality constraints + fnList freeNamesIfType (map snd eq_spec) &&& -- equality constraints + fnList freeNamesIfBang bangs + +freeNamesIfBang :: IfaceBang -> NameSet +freeNamesIfBang (IfUnpackCo co) = freeNamesIfCoercion co +freeNamesIfBang _ = emptyNameSet freeNamesIfKind :: IfaceType -> NameSet freeNamesIfKind = freeNamesIfType From git at git.haskell.org Fri May 19 14:00:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 May 2017 14:00:21 +0000 (UTC) Subject: [commit: ghc] master: Fix scoping of data cons during kind checking (2501fb7) Message-ID: <20170519140021.754893A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2501fb70691f80b9c48e5f9bdea3b897653f499a/ghc >--------------------------------------------------------------- commit 2501fb70691f80b9c48e5f9bdea3b897653f499a Author: Simon Peyton Jones Date: Fri May 19 14:57:59 2017 +0100 Fix scoping of data cons during kind checking Trac #13625 pointed out that in data X :: Y where Y :: X we need 'Y' to be in scope (as APromotionErr) when dealing with X's kind signature. Previously we got a crash. This patch simplifies the code as well as making it work. >--------------------------------------------------------------- 2501fb70691f80b9c48e5f9bdea3b897653f499a compiler/typecheck/TcEnv.hs | 24 ++++-- compiler/typecheck/TcRnTypes.hs | 4 +- compiler/typecheck/TcTyClsDecls.hs | 143 ++++++++++++++++++-------------- testsuite/tests/polykinds/T13625.hs | 5 ++ testsuite/tests/polykinds/T13625.stderr | 5 ++ testsuite/tests/polykinds/all.T | 1 + 6 files changed, 109 insertions(+), 73 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 2501fb70691f80b9c48e5f9bdea3b897653f499a From git at git.haskell.org Fri May 19 14:55:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 May 2017 14:55:16 +0000 (UTC) Subject: [commit: ghc] master: Modern type signature style in Module (4e0e120) Message-ID: <20170519145516.852F73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4e0e120bcbda6c5351d7c5aa01f7298e2198d457/ghc >--------------------------------------------------------------- commit 4e0e120bcbda6c5351d7c5aa01f7298e2198d457 Author: Bartosz Nitka Date: Fri May 19 07:54:06 2017 -0700 Modern type signature style in Module >--------------------------------------------------------------- 4e0e120bcbda6c5351d7c5aa01f7298e2198d457 compiler/basicTypes/Module.hs | 21 ++++++++++++--------- 1 file changed, 12 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/Module.hs b/compiler/basicTypes/Module.hs index e7f8a8d..4a3212f 100644 --- a/compiler/basicTypes/Module.hs +++ b/compiler/basicTypes/Module.hs @@ -1249,17 +1249,20 @@ isEmptyModuleEnv (ModuleEnv e) = Map.null e -- | A set of 'Module's type ModuleSet = Set NDModule -mkModuleSet :: [Module] -> ModuleSet -extendModuleSet :: ModuleSet -> Module -> ModuleSet -emptyModuleSet :: ModuleSet -moduleSetElts :: ModuleSet -> [Module] -elemModuleSet :: Module -> ModuleSet -> Bool +mkModuleSet :: [Module] -> ModuleSet +mkModuleSet = Set.fromList . coerce -emptyModuleSet = Set.empty -mkModuleSet = Set.fromList . coerce +extendModuleSet :: ModuleSet -> Module -> ModuleSet extendModuleSet s m = Set.insert (NDModule m) s -moduleSetElts = sort . coerce . Set.toList -elemModuleSet = Set.member . coerce + +emptyModuleSet :: ModuleSet +emptyModuleSet = Set.empty + +moduleSetElts :: ModuleSet -> [Module] +moduleSetElts = sort . coerce . Set.toList + +elemModuleSet :: Module -> ModuleSet -> Bool +elemModuleSet = Set.member . coerce {- A ModuleName has a Unique, so we can build mappings of these using From git at git.haskell.org Fri May 19 22:09:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 May 2017 22:09:19 +0000 (UTC) Subject: [commit: ghc] master: Improve error msg for simplifier tick exhaustion (40210c3) Message-ID: <20170519220919.68CDD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/40210c3637d7ac066e0d98c33612b57725708216/ghc >--------------------------------------------------------------- commit 40210c3637d7ac066e0d98c33612b57725708216 Author: David Feuer Date: Fri May 19 18:09:43 2017 -0400 Improve error msg for simplifier tick exhaustion Simplifier tick exhaustion is not necessarily "impossible", and isn't even always a GHC bug, per se. Improve the error message. Furthermore, the simplifier code has access to `IO`, so we can throw a proper `IO` exception instead of panicking. Reviewers: austin, bgamari, angerman Reviewed By: angerman Subscribers: angerman, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3597 >--------------------------------------------------------------- 40210c3637d7ac066e0d98c33612b57725708216 compiler/simplCore/SimplMonad.hs | 33 ++++++++++++++++++++++++--------- 1 file changed, 24 insertions(+), 9 deletions(-) diff --git a/compiler/simplCore/SimplMonad.hs b/compiler/simplCore/SimplMonad.hs index 8f20637..015ee5c 100644 --- a/compiler/simplCore/SimplMonad.hs +++ b/compiler/simplCore/SimplMonad.hs @@ -33,6 +33,7 @@ import Outputable import FastString import MonadUtils import ErrUtils +import Panic (throwGhcExceptionIO, GhcException (..)) import BasicTypes ( IntWithInf, treatZeroAsInf, mkIntWithInf ) import Control.Monad ( when, liftM, ap ) @@ -211,16 +212,30 @@ tick t = SM (\st_env us sc -> let sc' = doSimplTick (st_flags st_env) t sc checkedTick :: Tick -> SimplM () -- Try to take a tick, but fail if too many checkedTick t - = SM (\st_env us sc -> if st_max_ticks st_env <= mkIntWithInf (simplCountN sc) - then pprPanic "Simplifier ticks exhausted" (msg sc) - else let sc' = doSimplTick (st_flags st_env) t sc - in sc' `seq` return ((), us, sc')) + = SM (\st_env us sc -> + if st_max_ticks st_env <= mkIntWithInf (simplCountN sc) + then throwGhcExceptionIO $ + PprProgramError "Simplifier ticks exhausted" (msg sc) + else let sc' = doSimplTick (st_flags st_env) t sc + in sc' `seq` return ((), us, sc')) where - msg sc = vcat [ text "When trying" <+> ppr t - , text "To increase the limit, use -fsimpl-tick-factor=N (default 100)" - , text "If you need to do this, let GHC HQ know, and what factor you needed" - , pp_details sc - , pprSimplCount sc ] + msg sc = vcat + [ text "When trying" <+> ppr t + , text "To increase the limit, use -fsimpl-tick-factor=N (default 100)." + , space + , text "If you need to increase the limit substantially, please file a" + , text "bug report and indicate the factor you needed." + , space + , text "If GHC was unable to complete compilation even" + <+> text "with a very large factor" + , text "(a thousand or more), please consult the" + <+> doubleQuotes (text "Known bugs or infelicities") + , text "section in the Users Guide before filing a report. There are a" + , text "few situations unlikely to occur in practical programs for which" + , text "simplifier non-termination has been judged acceptable." + , space + , pp_details sc + , pprSimplCount sc ] pp_details sc | hasDetailedCounts sc = empty | otherwise = text "To see detailed counts use -ddump-simpl-stats" From git at git.haskell.org Sat May 20 16:42:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 May 2017 16:42:26 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Revert "Use a deterministic map for imp_dep_mods" (6cb4271) Message-ID: <20170520164226.318943A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/6cb4271194364e65ce150c3323d136749444aed0/ghc >--------------------------------------------------------------- commit 6cb4271194364e65ce150c3323d136749444aed0 Author: Bartosz Nitka Date: Mon May 15 04:44:35 2017 -0700 Revert "Use a deterministic map for imp_dep_mods" This reverts commit 7fea7121ce195e562a5443c0a8ef3861504ef1b3. It turns out that on a newly added MultiLayerModules test case it gets very expensive to union the transitive module sets while preserving determinism. Fortunately, we can just sort to restore determinism when converting imp_dep_mods to a list. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3577 (cherry picked from commit 8bf50d5026f92eb5a6768eb2ac38479802da1411) >--------------------------------------------------------------- 6cb4271194364e65ce150c3323d136749444aed0 compiler/deSugar/DsUsage.hs | 4 ++-- compiler/iface/MkIface.hs | 5 ++--- compiler/typecheck/TcRnDriver.hs | 14 +++++++------- compiler/typecheck/TcRnTypes.hs | 24 ++++++++++++++++-------- testsuite/tests/perf/compiler/all.T | 3 ++- 5 files changed, 29 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 6cb4271194364e65ce150c3323d136749444aed0 From git at git.haskell.org Sat May 20 16:42:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 May 2017 16:42:29 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Stress test for nested module hierarchies (6741d8a) Message-ID: <20170520164229.5631C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/6741d8ad5fe88b4f722aee7a823a4cd062c17216/ghc >--------------------------------------------------------------- commit 6741d8ad5fe88b4f722aee7a823a4cd062c17216 Author: Bartosz Nitka Date: Fri May 12 06:38:18 2017 -0700 Stress test for nested module hierarchies I'm optimizing a case that is well approximated by multiple layers of modules where every module in a layer imports all the modules in the layer below. It turns out I regressed performance on such cases in 7fea7121. I'm adding a test case to track improvements and prevent future regressions. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3575 (cherry picked from commit ffbcffffecf0307ff4dd3173503e2d3387d53386) >--------------------------------------------------------------- 6741d8ad5fe88b4f722aee7a823a4cd062c17216 testsuite/tests/perf/compiler/all.T | 11 +++++++++++ testsuite/tests/perf/compiler/genMultiLayerModules | 21 +++++++++++++++++++++ 2 files changed, 32 insertions(+) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index f8dbdd5..b65401f 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -1088,3 +1088,14 @@ test('T13379', ], compile, ['']) + +test('MultiLayerModules', + [ compiler_stats_num_field('bytes allocated', + [(wordsize(64), 12139116496, 10), + # initial: 12139116496 + ]), + pre_cmd('./genMultiLayerModules'), + extra_files(['genMultiLayerModules']), + ], + multimod_compile, + ['MultiLayerModules', '-v0']) diff --git a/testsuite/tests/perf/compiler/genMultiLayerModules b/testsuite/tests/perf/compiler/genMultiLayerModules new file mode 100755 index 0000000..b98c481 --- /dev/null +++ b/testsuite/tests/perf/compiler/genMultiLayerModules @@ -0,0 +1,21 @@ +#!/bin/bash +# Generate $DEPTH layers of modules with $WIDTH modules on each layer +# Every module on layer N imports all the modules on layer N-1 +# MultiLayerModules.hs imports all the modules from the last layer +DEPTH=15 +WIDTH=40 +for i in $(seq -w 1 $WIDTH); do + echo "module DummyLevel0M$i where" > DummyLevel0M$i.hs; +done +for l in $(seq 1 $DEPTH); do + for i in $(seq -w 1 $WIDTH); do + echo "module DummyLevel${l}M$i where" > DummyLevel${l}M$i.hs; + for j in $(seq -w 1 $WIDTH); do + echo "import DummyLevel$((l-1))M$j" >> DummyLevel${l}M$i.hs; + done + done +done +echo "module MultiLayerModules where" > MultiLayerModules.hs +for j in $(seq -w 1 $WIDTH); do + echo "import DummyLevel${DEPTH}M$j" >> MultiLayerModules.hs; +done From git at git.haskell.org Sat May 20 16:42:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 May 2017 16:42:33 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix #13703 by correctly using munged names in ghc-pkg. (8054a74) Message-ID: <20170520164233.3A4473A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/8054a7435dc15bc45c04adabe098a78ff6d6a7eb/ghc >--------------------------------------------------------------- commit 8054a7435dc15bc45c04adabe098a78ff6d6a7eb Author: Edward Z. Yang Date: Mon May 15 21:17:45 2017 -0700 Fix #13703 by correctly using munged names in ghc-pkg. Summary: Cabal internal libraries are implemented using a trick, where the 'name' field in ghc-pkg registration file is munged into a new form to keep each internal library looking like a distinct package to ghc-pkg and other tools; e.g. the internal library q from package p is named z-p-z-q. Later, Cabal library got refactored so that we made a closer distinction between these "munged" package names and the true package name of a package. Unfortunately, this is an example of a refactor for clarity in the source code which ends up causing problems downstream, because the point of "munging" the package name was to make it so that ghc-pkg and similar tools transparently used MungedPackageName whereever they previously used PackageName (in preparation for them learning proper syntax for package name + component name). Failing to do this meant that internal libraries from the same package (but with different names) clobber each other. This commit search-replaces most occurrences of PackageName in ghc-pkg and turns them into MungedPackageName. Otherwise there shouldn't be any functional differenes. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: bgamari, austin Subscribers: rwbarton, thomie GHC Trac Issues: #13703 Differential Revision: https://phabricator.haskell.org/D3590 (cherry picked from commit d9e9a9b3016a05e6153de3803998877f91c6cdf4) >--------------------------------------------------------------- 8054a7435dc15bc45c04adabe098a78ff6d6a7eb testsuite/.gitignore | 1 + testsuite/tests/cabal/Makefile | 8 +++++ testsuite/tests/cabal/T13703.stdout | 4 +++ testsuite/tests/cabal/all.T | 2 ++ testsuite/tests/cabal/test13703a.pkg | 20 +++++++++++ testsuite/tests/cabal/test13703b.pkg | 20 +++++++++++ utils/ghc-pkg/Main.hs | 66 +++++++++++++++++++----------------- 7 files changed, 89 insertions(+), 32 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 8054a7435dc15bc45c04adabe098a78ff6d6a7eb From git at git.haskell.org Sat May 20 18:10:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 May 2017 18:10:33 +0000 (UTC) Subject: [commit: ghc] master: Failing test case for #13734 (0a754e6) Message-ID: <20170520181033.36A113A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0a754e607ca40a344240925e99618c9e62c9690b/ghc >--------------------------------------------------------------- commit 0a754e607ca40a344240925e99618c9e62c9690b Author: Joachim Breitner Date: Sat May 20 14:09:21 2017 -0400 Failing test case for #13734 >--------------------------------------------------------------- 0a754e607ca40a344240925e99618c9e62c9690b testsuite/tests/simplCore/should_run/T13733.hs | 15 +++++++++++++++ .../should_run/T13733.stdout} | 0 testsuite/tests/simplCore/should_run/all.T | 1 + 3 files changed, 16 insertions(+) diff --git a/testsuite/tests/simplCore/should_run/T13733.hs b/testsuite/tests/simplCore/should_run/T13733.hs new file mode 100644 index 0000000..80c7791 --- /dev/null +++ b/testsuite/tests/simplCore/should_run/T13733.hs @@ -0,0 +1,15 @@ +module Main where + +delayedId :: a -> a +delayedId x = x +{-# INLINE [0] delayedId #-} + +alwaysTrue :: [Integer]-> Bool +alwaysTrue xs = xs == delayedId xs +{-# NOINLINE alwaysTrue #-} + +{-# RULES + "[Integer] Eq Refl" forall (xs :: [Integer]). xs == xs = True +#-} + +main = putStrLn $ if alwaysTrue undefined then "ok" else "not ok" diff --git a/testsuite/tests/codeGen/should_run/cgrun052.stdout b/testsuite/tests/simplCore/should_run/T13733.stdout similarity index 100% copy from testsuite/tests/codeGen/should_run/cgrun052.stdout copy to testsuite/tests/simplCore/should_run/T13733.stdout diff --git a/testsuite/tests/simplCore/should_run/all.T b/testsuite/tests/simplCore/should_run/all.T index 9317b8b..1ff71d8 100644 --- a/testsuite/tests/simplCore/should_run/all.T +++ b/testsuite/tests/simplCore/should_run/all.T @@ -73,3 +73,4 @@ test('T12689a', normal, compile_and_run, ['']) test('T13172', only_ways(['optasm']), compile_and_run, ['-dcore-lint']) test('T13227', normal, compile_and_run, ['']) +test('T13733', expect_broken(13733), compile_and_run, ['']) From git at git.haskell.org Sat May 20 20:29:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 May 2017 20:29:35 +0000 (UTC) Subject: [commit: ghc] master: Bump to LLVM 4.0 (82eab62) Message-ID: <20170520202935.1383E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/82eab628c20e2001c870f007bfb09f198f4c9c36/ghc >--------------------------------------------------------------- commit 82eab628c20e2001c870f007bfb09f198f4c9c36 Author: Moritz Angermann Date: Sat May 20 12:57:15 2017 -0400 Bump to LLVM 4.0 The llvm textual ir seems to have stayed sufficiently similar from llvm 3.9 to llvm 4.0, such that a simple bump is possible. Reviewers: austin, hvr, bgamari, erikd Reviewed By: bgamari, erikd Subscribers: rwbarton, thomie, erikd Differential Revision: https://phabricator.haskell.org/D3591 >--------------------------------------------------------------- 82eab628c20e2001c870f007bfb09f198f4c9c36 configure.ac | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/configure.ac b/configure.ac index 73ee64d..45b2ab3 100644 --- a/configure.ac +++ b/configure.ac @@ -574,7 +574,7 @@ RANLIB="$RanlibCmd" # tools we are looking for. In the past, GHC supported a number of # versions of LLVM simultaneously, but that stopped working around # 3.5/3.6 release of LLVM. -LlvmVersion=3.9 +LlvmVersion=4.0 AC_SUBST([LlvmVersion]) sUPPORTED_LLVM_VERSION=$(echo \($LlvmVersion\) | sed 's/\./,/') AC_DEFINE_UNQUOTED([sUPPORTED_LLVM_VERSION], ${sUPPORTED_LLVM_VERSION}, [The supported LLVM version number]) From git at git.haskell.org Sat May 20 20:29:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 May 2017 20:29:38 +0000 (UTC) Subject: [commit: ghc] master: Compile modules that are needed by template haskell, even with -fno-code. (53c78be) Message-ID: <20170520202938.70FD73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/53c78be0aab76a3107c4dacbb1d177afacdd37fa/ghc >--------------------------------------------------------------- commit 53c78be0aab76a3107c4dacbb1d177afacdd37fa Author: Douglas Wilson Date: Sat May 20 12:47:41 2017 -0400 Compile modules that are needed by template haskell, even with -fno-code. This patch relates to Trac #8025 The goal here is to enable typechecking of packages that contain some template haskell. Prior to this patch, compilation of a package with -fno-code would fail if any functions in the package were called from within a splice. downsweep is changed to do an additional pass over the modules, targetting any ModSummaries transitively depended on by a module that has LangExt.TemplateHaskell enabled. Those targeted modules have hscTarget changed from HscNothing to the default target of the platform. There is a small change to the prevailing_target logic to enable this. A simple test is added. I have benchmarked with and without a patched haddock (available:https://github.com/duog/haddock/tree/wip-no-explicit-th-compi lation). Running cabal haddock on the wreq package results in a 25% speedup on my machine: time output from patched cabal haddock: real 0m5.780s user 0m5.304s sys 0m0.496s time output from unpatched cabal haddock: real 0m7.712s user 0m6.888s sys 0m0.736s Reviewers: austin, bgamari, ezyang Reviewed By: bgamari Subscribers: bgamari, DanielG, rwbarton, thomie GHC Trac Issues: #8025 Differential Revision: https://phabricator.haskell.org/D3441 >--------------------------------------------------------------- 53c78be0aab76a3107c4dacbb1d177afacdd37fa compiler/backpack/DriverBkp.hs | 1 + compiler/main/DriverPipeline.hs | 73 +++++---- compiler/main/DynFlags.hs | 10 +- compiler/main/GhcMake.hs | 182 +++++++++++++++++++-- compiler/main/HscTypes.hs | 2 +- .../Sub1.hs => th/should_compile/T8025/A.hs} | 4 +- testsuite/tests/th/should_compile/T8025/B.hs | 5 + .../T12062 => th/should_compile/T8025}/Makefile | 0 testsuite/tests/th/should_compile/T8025/all.T | 2 + 9 files changed, 220 insertions(+), 59 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 53c78be0aab76a3107c4dacbb1d177afacdd37fa From git at git.haskell.org Sat May 20 20:29:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 May 2017 20:29:41 +0000 (UTC) Subject: [commit: ghc] master: base: Explicitly mark Data.Either.{left, right} as INLINABLE (80d5190) Message-ID: <20170520202941.2B4523A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/80d5190630a975dfa03d1d84d23cdee4f950d58d/ghc >--------------------------------------------------------------- commit 80d5190630a975dfa03d1d84d23cdee4f950d58d Author: Ben Gamari Date: Sat May 20 12:48:03 2017 -0400 base: Explicitly mark Data.Either.{left,right} as INLINABLE Test Plan: read it Reviewers: dfeuer, austin, hvr, nomeata Reviewed By: dfeuer, nomeata Subscribers: nomeata, rwbarton, thomie GHC Trac Issues: #13689 Differential Revision: https://phabricator.haskell.org/D3576 >--------------------------------------------------------------- 80d5190630a975dfa03d1d84d23cdee4f950d58d libraries/base/Data/Either.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/libraries/base/Data/Either.hs b/libraries/base/Data/Either.hs index 437d87c..2469e78 100644 --- a/libraries/base/Data/Either.hs +++ b/libraries/base/Data/Either.hs @@ -178,6 +178,7 @@ either _ g (Right y) = g y -- lefts :: [Either a b] -> [a] lefts x = [a | Left a <- x] +{-# INLINEABLE lefts #-} -- otherwise doesnt get an unfolding, see #13689 -- | Extracts from a list of 'Either' all the 'Right' elements. -- All the 'Right' elements are extracted in order. @@ -192,6 +193,7 @@ lefts x = [a | Left a <- x] -- rights :: [Either a b] -> [b] rights x = [a | Right a <- x] +{-# INLINEABLE rights #-} -- otherwise doesnt get an unfolding, see #13689 -- | Partitions a list of 'Either' into two lists. -- All the 'Left' elements are extracted, in order, to the first From git at git.haskell.org Sat May 20 20:29:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 May 2017 20:29:43 +0000 (UTC) Subject: [commit: ghc] master: CNF: Silence pointer fix-up message unless gc debugging is enabled (0102e2b) Message-ID: <20170520202943.E9C413A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0102e2b731d33abdff4c3cde6938d1bede8f51cb/ghc >--------------------------------------------------------------- commit 0102e2b731d33abdff4c3cde6938d1bede8f51cb Author: Ben Gamari Date: Wed May 17 10:22:55 2017 -0400 CNF: Silence pointer fix-up message unless gc debugging is enabled >--------------------------------------------------------------- 0102e2b731d33abdff4c3cde6938d1bede8f51cb libraries/ghc-compact/tests/compact_serialize.stderr | 1 - rts/sm/CNF.c | 4 ++-- 2 files changed, 2 insertions(+), 3 deletions(-) diff --git a/libraries/ghc-compact/tests/compact_serialize.stderr b/libraries/ghc-compact/tests/compact_serialize.stderr index 2483efa..e69de29 100644 --- a/libraries/ghc-compact/tests/compact_serialize.stderr +++ b/libraries/ghc-compact/tests/compact_serialize.stderr @@ -1 +0,0 @@ -Compact imported at the wrong address, will fix up internal pointers diff --git a/rts/sm/CNF.c b/rts/sm/CNF.c index bdb018d..cec0e31 100644 --- a/rts/sm/CNF.c +++ b/rts/sm/CNF.c @@ -1131,8 +1131,8 @@ maybe_fixup_internal_pointers (StgCompactNFDataBlock *block, if (!any_needs_fixup(block)) return root; - debugBelch("Compact imported at the wrong address, will fix up" - " internal pointers\n"); + IF_DEBUG(gc, debugBelch("Compact imported at the wrong address, " + "will fix up internal pointers\n")); // I am PROOT! proot = &root; From git at git.haskell.org Sat May 20 20:29:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 May 2017 20:29:47 +0000 (UTC) Subject: [commit: ghc] master: Pretty-print strict record fields from ifaces correctly (2108460) Message-ID: <20170520202947.56E1D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2108460f9211bf5eab98e0f2f3218dcd271eeaad/ghc >--------------------------------------------------------------- commit 2108460f9211bf5eab98e0f2f3218dcd271eeaad Author: Ryan Scott Date: Sat May 20 12:56:50 2017 -0400 Pretty-print strict record fields from ifaces correctly We need to use parentheses more when pretty-printing types with bang patterns within constructors that use record syntax. Fixes #13699. Test Plan: make test TEST=T13699 Reviewers: austin, bgamari, dfeuer Reviewed By: dfeuer Subscribers: dfeuer, rwbarton, thomie GHC Trac Issues: #13699 Differential Revision: https://phabricator.haskell.org/D3587 >--------------------------------------------------------------- 2108460f9211bf5eab98e0f2f3218dcd271eeaad compiler/iface/IfaceSyn.hs | 10 +++++++++- testsuite/tests/ghci/scripts/T13699.hs | 10 ++++++++++ testsuite/tests/ghci/scripts/T13699.script | 3 +++ testsuite/tests/ghci/scripts/T13699.stdout | 8 ++++++++ testsuite/tests/ghci/scripts/all.T | 1 + 5 files changed, 31 insertions(+), 1 deletion(-) diff --git a/compiler/iface/IfaceSyn.hs b/compiler/iface/IfaceSyn.hs index 338397d..60206ea 100644 --- a/compiler/iface/IfaceSyn.hs +++ b/compiler/iface/IfaceSyn.hs @@ -1003,7 +1003,15 @@ pprIfaceConDecl ss gadt_style tycon tc_binders parent pprParendIfaceCoercion co pprParendBangTy (bang, ty) = ppr_bang bang <> pprParendIfaceType ty - pprBangTy (bang, ty) = ppr_bang bang <> ppr ty + pprBangTy (bang, ty) = ppr_bang bang <> ppr_banged_ty ty + where + -- The presence of bang patterns or UNPACK annotations requires + -- surrounding the type with parentheses, if needed (#13699) + ppr_banged_ty = case bang of + IfNoBang -> ppr + IfStrict -> pprParendIfaceType + IfUnpack -> pprParendIfaceType + IfUnpackCo{} -> pprParendIfaceType pp_args :: [SDoc] -- With parens, e.g (Maybe a) or !(Maybe a) pp_args = map pprParendBangTy tys_w_strs diff --git a/testsuite/tests/ghci/scripts/T13699.hs b/testsuite/tests/ghci/scripts/T13699.hs new file mode 100644 index 0000000..0579399 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T13699.hs @@ -0,0 +1,10 @@ +module T13699 where + +data Foo = Foo + { foo1 :: Int + , foo2 :: !Int + , foo3 :: Maybe Int + , foo4 :: !(Maybe Int) + } + +data Bar = Bar Int !Int (Maybe Int) !(Maybe Int) diff --git a/testsuite/tests/ghci/scripts/T13699.script b/testsuite/tests/ghci/scripts/T13699.script new file mode 100644 index 0000000..8decf0b --- /dev/null +++ b/testsuite/tests/ghci/scripts/T13699.script @@ -0,0 +1,3 @@ +:load T13699 +:i Foo +:i Bar diff --git a/testsuite/tests/ghci/scripts/T13699.stdout b/testsuite/tests/ghci/scripts/T13699.stdout new file mode 100644 index 0000000..b5950a7 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T13699.stdout @@ -0,0 +1,8 @@ +data Foo + = Foo {foo1 :: Int, + foo2 :: !Int, + foo3 :: Maybe Int, + foo4 :: !(Maybe Int)} + -- Defined at T13699.hs:3:1 +data Bar = Bar Int !Int (Maybe Int) !(Maybe Int) + -- Defined at T13699.hs:10:1 diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index ae0a528..8ef45fe 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -255,3 +255,4 @@ test('T13420', normal, ghci_script, ['T13420.script']) test('T13466', normal, ghci_script, ['T13466.script']) test('GhciCurDir', normal, ghci_script, ['GhciCurDir.script']) test('T13591', expect_broken(13591), ghci_script, ['T13591.script']) +test('T13699', normal, ghci_script, ['T13699.script']) From git at git.haskell.org Sat May 20 20:29:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 May 2017 20:29:52 +0000 (UTC) Subject: [commit: ghc] master: Correctly expand lines with multiple tabs (8646648) Message-ID: <20170520202952.C45953A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/86466489a4154d595c408470df68e946a100df88/ghc >--------------------------------------------------------------- commit 86466489a4154d595c408470df68e946a100df88 Author: Phil Ruffwind Date: Sat May 20 12:48:26 2017 -0400 Correctly expand lines with multiple tabs rwbarton pointed out that tab expansions can affect the column numbers of subsequent characters, so a unstateful map + zip won't do. This commit hopefully fixes that. It also adds a test for this particular case. Test Plan: validate Reviewers: bgamari, rwbarton, austin Reviewed By: bgamari Subscribers: dfeuer, thomie Differential Revision: https://phabricator.haskell.org/D3578 >--------------------------------------------------------------- 86466489a4154d595c408470df68e946a100df88 compiler/main/ErrUtils.hs | 17 ++++++++++------- .../tests/warnings/should_fail/CaretDiagnostics1.hs | 3 +++ .../tests/warnings/should_fail/CaretDiagnostics1.stderr | 8 ++++++++ 3 files changed, 21 insertions(+), 7 deletions(-) diff --git a/compiler/main/ErrUtils.hs b/compiler/main/ErrUtils.hs index d87d2b2..b0bbe3c 100644 --- a/compiler/main/ErrUtils.hs +++ b/compiler/main/ErrUtils.hs @@ -278,13 +278,16 @@ getCaretDiagnostic severity (RealSrcSpan span) = do where - fixWhitespace (i, c) - | c == '\n' = "" - -- show tabs in a device-independent manner #13664 - | c == '\t' = replicate (8 - i `mod` 8) ' ' - | otherwise = [c] - - srcLine = concat (map fixWhitespace (zip [0..] srcLineWithNewline)) + -- expand tabs in a device-independent manner #13664 + expandTabs tabWidth i s = + case s of + "" -> "" + '\t' : cs -> replicate effectiveWidth ' ' ++ + expandTabs tabWidth (i + effectiveWidth) cs + c : cs -> c : expandTabs tabWidth (i + 1) cs + where effectiveWidth = tabWidth - i `mod` tabWidth + + srcLine = filter (/= '\n') (expandTabs 8 0 srcLineWithNewline) start = srcSpanStartCol span - 1 end | multiline = length srcLine diff --git a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs index 3ebb5ee..baa8a33 100644 --- a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs +++ b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs @@ -18,3 +18,6 @@ fóo = () tabby :: Int tabby = () + +tabby2 :: Int +tabby2 = () diff --git a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr index 600b7c7..15dedf0 100644 --- a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr +++ b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr @@ -78,3 +78,11 @@ CaretDiagnostics1.hs:20:17-18: error: | 20 | tabby = () | ^^ + +CaretDiagnostics1.hs:23:25-26: error: + • Couldn't match expected type ‘Int’ with actual type ‘()’ + • In the expression: () + In an equation for ‘tabby2’: tabby2 = () + | +23 | tabby2 = () + | ^^ From git at git.haskell.org Sat May 20 20:29:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 May 2017 20:29:50 +0000 (UTC) Subject: [commit: ghc] master: A few documentation fixes (5b8f95d) Message-ID: <20170520202950.1354C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5b8f95d7fca302a9ad27533b74b1a1c2364605dc/ghc >--------------------------------------------------------------- commit 5b8f95d7fca302a9ad27533b74b1a1c2364605dc Author: David Feuer Date: Sat May 20 12:56:20 2017 -0400 A few documentation fixes `MIN_VERSION_pkg` was documented backwards. An important caveat about initializing the Haskell runtime was buried in a footnote. The documentation of `-dynamic` was (even more) confusing. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3582 >--------------------------------------------------------------- 5b8f95d7fca302a9ad27533b74b1a1c2364605dc docs/users_guide/bugs.rst | 2 +- docs/users_guide/ffi-chap.rst | 11 ++++------- docs/users_guide/phases.rst | 8 ++++++-- 3 files changed, 11 insertions(+), 10 deletions(-) diff --git a/docs/users_guide/bugs.rst b/docs/users_guide/bugs.rst index 707f66b..7ccb215 100644 --- a/docs/users_guide/bugs.rst +++ b/docs/users_guide/bugs.rst @@ -342,7 +342,7 @@ The Foreign Function Interface ``hs_init()``, ``hs_exit()`` The FFI spec requires the implementation to support re-initialising itself after being shut down with ``hs_exit()``, but GHC does not - currently support that. + currently support that. See :ghc-ticket:`13693`. .. index:: single: hs_init diff --git a/docs/users_guide/ffi-chap.rst b/docs/users_guide/ffi-chap.rst index d4bf343..35557b8 100644 --- a/docs/users_guide/ffi-chap.rst +++ b/docs/users_guide/ffi-chap.rst @@ -311,8 +311,10 @@ can separate out any arguments for the RTS (i.e. those arguments between After we've finished invoking our Haskell functions, we can call ``hs_exit()``, which terminates the RTS. -There can be multiple calls to ``hs_init()``, but each one should be -matched by one (and only one) call to ``hs_exit()`` [1]_. +There can be multiple calls to ``hs_init()``, but each one should be matched by +one (and only one) call to ``hs_exit()``. The outermost ``hs_exit()`` will +actually de-initialise the system. Note that currently GHC's runtime cannot +reliably re-initialise after this has happened; see :ref:`infelicities-ffi`. .. note:: When linking the final program, it is normally easiest to do the @@ -320,11 +322,6 @@ matched by one (and only one) call to ``hs_exit()`` [1]_. don't forget the flag :ghc-flag:`-no-hs-main`, otherwise GHC will try to link to the ``Main`` Haskell module. -.. [1] - The outermost ``hs_exit()`` will actually de-initialise the system. - Note that currently GHC's runtime cannot reliably re-initialise after - this has happened, see :ref:`infelicities-ffi`. - To use ``+RTS`` flags with ``hs_init()``, we have to modify the example slightly. By default, GHC's RTS will only accept "safe" ``+RTS`` flags (see :ref:`options-linker`), and the :ghc-flag:`-rtsopts` diff --git a/docs/users_guide/phases.rst b/docs/users_guide/phases.rst index 6bc9767..1efe6a4 100644 --- a/docs/users_guide/phases.rst +++ b/docs/users_guide/phases.rst @@ -324,7 +324,7 @@ defined by your local GHC installation, the following trick is useful: This macro is available starting GHC 8.0. It is defined for every exposed package. This macro is provided for convenience to write CPP conditionals testing if a package version is ``x.y.z`` or - less. It is identical in behavior to the ``MIN_VERSION_pkgname`` + later. It is identical in behavior to the ``MIN_VERSION_pkgname`` macros that Cabal defines. .. _cpp-string-gaps: @@ -459,7 +459,11 @@ Options affecting code generation :noindex: When generating code, assume that entities imported from a different - package will reside in a different shared library or binary. + package will be dynamically linked. This can reduce code size + tremendously, but may slow-down cross-package calls of non-inlined + functions. There can be some complications combining :ghc-flag:`-shared` + with this flag relating to linking in the RTS under Linux. See + :ghc-ticket:`10352`. Note that using this option when linking causes GHC to link against shared libraries. From git at git.haskell.org Sun May 21 15:08:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 21 May 2017 15:08:41 +0000 (UTC) Subject: [commit: ghc] master: Fix levity polymorphism docs (6f8c3ce) Message-ID: <20170521150841.B00633A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6f8c3ce4b1dac02acf93c351862d3b6c46815840/ghc >--------------------------------------------------------------- commit 6f8c3ce4b1dac02acf93c351862d3b6c46815840 Author: Alexey Vagarenko Date: Sun May 21 15:08:41 2017 +0500 Fix levity polymorphism docs >--------------------------------------------------------------- 6f8c3ce4b1dac02acf93c351862d3b6c46815840 docs/users_guide/glasgow_exts.rst | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 729cd4d..d9a70c3 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -8446,7 +8446,7 @@ think about compiling this to runnable code, though, problems appear. In particular, when we call ``bad``, we must somehow pass ``x`` into ``bad``. How wide (that is, how many bits) is ``x``? Is it a pointer? What kind of register (floating-point or integral) should ``x`` go in? -It's all impossible to say, because ``x``'s type, ``TYPE r2`` is +It's all impossible to say, because ``x``'s type, ``a :: TYPE r1`` is levity polymorphic. We thus forbid such constructions, via the following straightforward rule: From git at git.haskell.org Sun May 21 15:10:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 21 May 2017 15:10:03 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: CNF: Silence pointer fix-up message unless gc debugging is enabled (4bf470c) Message-ID: <20170521151003.F3DC73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/4bf470c66dd409b3c8734549762d798eb3c64cde/ghc >--------------------------------------------------------------- commit 4bf470c66dd409b3c8734549762d798eb3c64cde Author: Ben Gamari Date: Wed May 17 10:22:55 2017 -0400 CNF: Silence pointer fix-up message unless gc debugging is enabled (cherry picked from commit 0102e2b731d33abdff4c3cde6938d1bede8f51cb) >--------------------------------------------------------------- 4bf470c66dd409b3c8734549762d798eb3c64cde libraries/ghc-compact/tests/compact_serialize.stderr | 1 - rts/sm/CNF.c | 4 ++-- 2 files changed, 2 insertions(+), 3 deletions(-) diff --git a/libraries/ghc-compact/tests/compact_serialize.stderr b/libraries/ghc-compact/tests/compact_serialize.stderr index 2483efa..e69de29 100644 --- a/libraries/ghc-compact/tests/compact_serialize.stderr +++ b/libraries/ghc-compact/tests/compact_serialize.stderr @@ -1 +0,0 @@ -Compact imported at the wrong address, will fix up internal pointers diff --git a/rts/sm/CNF.c b/rts/sm/CNF.c index fbebfab..3892132 100644 --- a/rts/sm/CNF.c +++ b/rts/sm/CNF.c @@ -1125,8 +1125,8 @@ maybe_fixup_internal_pointers (StgCompactNFDataBlock *block, if (!any_needs_fixup(block)) return root; - debugBelch("Compact imported at the wrong address, will fix up" - " internal pointers\n"); + IF_DEBUG(gc, debugBelch("Compact imported at the wrong address, " + "will fix up internal pointers\n")); // I am PROOT! proot = &root; From git at git.haskell.org Sun May 21 15:10:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 21 May 2017 15:10:12 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: base: Explicitly mark Data.Either.{left, right} as INLINABLE (fdcdcd0) Message-ID: <20170521151012.52EC03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/fdcdcd0f8fdb08125932b7f8a3f5a8adc5d50466/ghc >--------------------------------------------------------------- commit fdcdcd0f8fdb08125932b7f8a3f5a8adc5d50466 Author: Ben Gamari Date: Sat May 20 12:48:03 2017 -0400 base: Explicitly mark Data.Either.{left,right} as INLINABLE Test Plan: read it Reviewers: dfeuer, austin, hvr, nomeata Reviewed By: dfeuer, nomeata Subscribers: nomeata, rwbarton, thomie GHC Trac Issues: #13689 Differential Revision: https://phabricator.haskell.org/D3576 (cherry picked from commit 80d5190630a975dfa03d1d84d23cdee4f950d58d) >--------------------------------------------------------------- fdcdcd0f8fdb08125932b7f8a3f5a8adc5d50466 libraries/base/Data/Either.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/libraries/base/Data/Either.hs b/libraries/base/Data/Either.hs index 437d87c..2469e78 100644 --- a/libraries/base/Data/Either.hs +++ b/libraries/base/Data/Either.hs @@ -178,6 +178,7 @@ either _ g (Right y) = g y -- lefts :: [Either a b] -> [a] lefts x = [a | Left a <- x] +{-# INLINEABLE lefts #-} -- otherwise doesnt get an unfolding, see #13689 -- | Extracts from a list of 'Either' all the 'Right' elements. -- All the 'Right' elements are extracted in order. @@ -192,6 +193,7 @@ lefts x = [a | Left a <- x] -- rights :: [Either a b] -> [b] rights x = [a | Right a <- x] +{-# INLINEABLE rights #-} -- otherwise doesnt get an unfolding, see #13689 -- | Partitions a list of 'Either' into two lists. -- All the 'Left' elements are extracted, in order, to the first From git at git.haskell.org Sun May 21 15:10:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 21 May 2017 15:10:09 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Correctly expand lines with multiple tabs (02837ea) Message-ID: <20170521151009.93BA13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/02837ea502e8c38d8e256251166079504fd03015/ghc >--------------------------------------------------------------- commit 02837ea502e8c38d8e256251166079504fd03015 Author: Phil Ruffwind Date: Sat May 20 12:48:26 2017 -0400 Correctly expand lines with multiple tabs rwbarton pointed out that tab expansions can affect the column numbers of subsequent characters, so a unstateful map + zip won't do. This commit hopefully fixes that. It also adds a test for this particular case. Test Plan: validate Reviewers: bgamari, rwbarton, austin Reviewed By: bgamari Subscribers: dfeuer, thomie Differential Revision: https://phabricator.haskell.org/D3578 (cherry picked from commit 86466489a4154d595c408470df68e946a100df88) >--------------------------------------------------------------- 02837ea502e8c38d8e256251166079504fd03015 compiler/main/ErrUtils.hs | 17 ++++++++++------- .../tests/warnings/should_fail/CaretDiagnostics1.hs | 3 +++ .../tests/warnings/should_fail/CaretDiagnostics1.stderr | 8 ++++++++ 3 files changed, 21 insertions(+), 7 deletions(-) diff --git a/compiler/main/ErrUtils.hs b/compiler/main/ErrUtils.hs index d87d2b2..b0bbe3c 100644 --- a/compiler/main/ErrUtils.hs +++ b/compiler/main/ErrUtils.hs @@ -278,13 +278,16 @@ getCaretDiagnostic severity (RealSrcSpan span) = do where - fixWhitespace (i, c) - | c == '\n' = "" - -- show tabs in a device-independent manner #13664 - | c == '\t' = replicate (8 - i `mod` 8) ' ' - | otherwise = [c] - - srcLine = concat (map fixWhitespace (zip [0..] srcLineWithNewline)) + -- expand tabs in a device-independent manner #13664 + expandTabs tabWidth i s = + case s of + "" -> "" + '\t' : cs -> replicate effectiveWidth ' ' ++ + expandTabs tabWidth (i + effectiveWidth) cs + c : cs -> c : expandTabs tabWidth (i + 1) cs + where effectiveWidth = tabWidth - i `mod` tabWidth + + srcLine = filter (/= '\n') (expandTabs 8 0 srcLineWithNewline) start = srcSpanStartCol span - 1 end | multiline = length srcLine diff --git a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs index 3ebb5ee..baa8a33 100644 --- a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs +++ b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.hs @@ -18,3 +18,6 @@ fóo = () tabby :: Int tabby = () + +tabby2 :: Int +tabby2 = () diff --git a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr index 600b7c7..15dedf0 100644 --- a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr +++ b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr @@ -78,3 +78,11 @@ CaretDiagnostics1.hs:20:17-18: error: | 20 | tabby = () | ^^ + +CaretDiagnostics1.hs:23:25-26: error: + • Couldn't match expected type ‘Int’ with actual type ‘()’ + • In the expression: () + In an equation for ‘tabby2’: tabby2 = () + | +23 | tabby2 = () + | ^^ From git at git.haskell.org Sun May 21 15:10:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 21 May 2017 15:10:15 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix scoping of data cons during kind checking (2fb2b60) Message-ID: <20170521151015.E1EF73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/2fb2b60ebc6a649b8345bbb491a253972c973978/ghc >--------------------------------------------------------------- commit 2fb2b60ebc6a649b8345bbb491a253972c973978 Author: Simon Peyton Jones Date: Fri May 19 14:57:59 2017 +0100 Fix scoping of data cons during kind checking Trac #13625 pointed out that in data X :: Y where Y :: X we need 'Y' to be in scope (as APromotionErr) when dealing with X's kind signature. Previously we got a crash. This patch simplifies the code as well as making it work. (cherry picked from commit 2501fb70691f80b9c48e5f9bdea3b897653f499a) >--------------------------------------------------------------- 2fb2b60ebc6a649b8345bbb491a253972c973978 compiler/typecheck/TcEnv.hs | 24 ++++-- compiler/typecheck/TcRnTypes.hs | 4 +- compiler/typecheck/TcTyClsDecls.hs | 143 ++++++++++++++++++-------------- testsuite/tests/polykinds/T13625.hs | 5 ++ testsuite/tests/polykinds/T13625.stderr | 5 ++ testsuite/tests/polykinds/all.T | 1 + 6 files changed, 109 insertions(+), 73 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 2fb2b60ebc6a649b8345bbb491a253972c973978 From git at git.haskell.org Sun May 21 15:10:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 21 May 2017 15:10:06 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: A few documentation fixes (d4d8936) Message-ID: <20170521151006.BE70F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/d4d8936d64fbd5e2104560b02cf7b2972e391945/ghc >--------------------------------------------------------------- commit d4d8936d64fbd5e2104560b02cf7b2972e391945 Author: David Feuer Date: Sat May 20 12:56:20 2017 -0400 A few documentation fixes `MIN_VERSION_pkg` was documented backwards. An important caveat about initializing the Haskell runtime was buried in a footnote. The documentation of `-dynamic` was (even more) confusing. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3582 (cherry picked from commit 5b8f95d7fca302a9ad27533b74b1a1c2364605dc) >--------------------------------------------------------------- d4d8936d64fbd5e2104560b02cf7b2972e391945 docs/users_guide/bugs.rst | 2 +- docs/users_guide/ffi-chap.rst | 11 ++++------- docs/users_guide/phases.rst | 8 ++++++-- 3 files changed, 11 insertions(+), 10 deletions(-) diff --git a/docs/users_guide/bugs.rst b/docs/users_guide/bugs.rst index 707f66b..7ccb215 100644 --- a/docs/users_guide/bugs.rst +++ b/docs/users_guide/bugs.rst @@ -342,7 +342,7 @@ The Foreign Function Interface ``hs_init()``, ``hs_exit()`` The FFI spec requires the implementation to support re-initialising itself after being shut down with ``hs_exit()``, but GHC does not - currently support that. + currently support that. See :ghc-ticket:`13693`. .. index:: single: hs_init diff --git a/docs/users_guide/ffi-chap.rst b/docs/users_guide/ffi-chap.rst index d4bf343..35557b8 100644 --- a/docs/users_guide/ffi-chap.rst +++ b/docs/users_guide/ffi-chap.rst @@ -311,8 +311,10 @@ can separate out any arguments for the RTS (i.e. those arguments between After we've finished invoking our Haskell functions, we can call ``hs_exit()``, which terminates the RTS. -There can be multiple calls to ``hs_init()``, but each one should be -matched by one (and only one) call to ``hs_exit()`` [1]_. +There can be multiple calls to ``hs_init()``, but each one should be matched by +one (and only one) call to ``hs_exit()``. The outermost ``hs_exit()`` will +actually de-initialise the system. Note that currently GHC's runtime cannot +reliably re-initialise after this has happened; see :ref:`infelicities-ffi`. .. note:: When linking the final program, it is normally easiest to do the @@ -320,11 +322,6 @@ matched by one (and only one) call to ``hs_exit()`` [1]_. don't forget the flag :ghc-flag:`-no-hs-main`, otherwise GHC will try to link to the ``Main`` Haskell module. -.. [1] - The outermost ``hs_exit()`` will actually de-initialise the system. - Note that currently GHC's runtime cannot reliably re-initialise after - this has happened, see :ref:`infelicities-ffi`. - To use ``+RTS`` flags with ``hs_init()``, we have to modify the example slightly. By default, GHC's RTS will only accept "safe" ``+RTS`` flags (see :ref:`options-linker`), and the :ghc-flag:`-rtsopts` diff --git a/docs/users_guide/phases.rst b/docs/users_guide/phases.rst index 6bc9767..1efe6a4 100644 --- a/docs/users_guide/phases.rst +++ b/docs/users_guide/phases.rst @@ -324,7 +324,7 @@ defined by your local GHC installation, the following trick is useful: This macro is available starting GHC 8.0. It is defined for every exposed package. This macro is provided for convenience to write CPP conditionals testing if a package version is ``x.y.z`` or - less. It is identical in behavior to the ``MIN_VERSION_pkgname`` + later. It is identical in behavior to the ``MIN_VERSION_pkgname`` macros that Cabal defines. .. _cpp-string-gaps: @@ -459,7 +459,11 @@ Options affecting code generation :noindex: When generating code, assume that entities imported from a different - package will reside in a different shared library or binary. + package will be dynamically linked. This can reduce code size + tremendously, but may slow-down cross-package calls of non-inlined + functions. There can be some complications combining :ghc-flag:`-shared` + with this flag relating to linking in the RTS under Linux. See + :ghc-ticket:`10352`. Note that using this option when linking causes GHC to link against shared libraries. From git at git.haskell.org Sun May 21 15:10:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 21 May 2017 15:10:18 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix levity polymorphism docs (cac103f) Message-ID: <20170521151018.9D1E83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/cac103f1bd2b7fa9dbe8cf17b4829c9175205257/ghc >--------------------------------------------------------------- commit cac103f1bd2b7fa9dbe8cf17b4829c9175205257 Author: Alexey Vagarenko Date: Sun May 21 15:08:41 2017 +0500 Fix levity polymorphism docs (cherry picked from commit 6f8c3ce4b1dac02acf93c351862d3b6c46815840) >--------------------------------------------------------------- cac103f1bd2b7fa9dbe8cf17b4829c9175205257 docs/users_guide/glasgow_exts.rst | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 89b243b..4a7ef74 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -8351,7 +8351,7 @@ think about compiling this to runnable code, though, problems appear. In particular, when we call ``bad``, we must somehow pass ``x`` into ``bad``. How wide (that is, how many bits) is ``x``? Is it a pointer? What kind of register (floating-point or integral) should ``x`` go in? -It's all impossible to say, because ``x``'s type, ``TYPE r2`` is +It's all impossible to say, because ``x``'s type, ``a :: TYPE r1`` is levity polymorphic. We thus forbid such constructions, via the following straightforward rule: From git at git.haskell.org Mon May 22 10:21:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 May 2017 10:21:09 +0000 (UTC) Subject: [commit: ghc] master: Add missing "do" to example in arrow docs. (5179fd4) Message-ID: <20170522102109.43E673A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5179fd4d71ae67bfb34cedf1e1d4f3b3de8e974d/ghc >--------------------------------------------------------------- commit 5179fd4d71ae67bfb34cedf1e1d4f3b3de8e974d Author: null-a Date: Mon May 22 10:13:14 2017 +0100 Add missing "do" to example in arrow docs. >--------------------------------------------------------------- 5179fd4d71ae67bfb34cedf1e1d4f3b3de8e974d docs/users_guide/glasgow_exts.rst | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index d9a70c3..20312eb 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -11671,7 +11671,7 @@ abstraction. We could define our own operator :: untilA :: ArrowChoice a => a (e,s) () -> a (e,s) Bool -> a (e,s) () - untilA body cond = proc x -> + untilA body cond = proc x -> do b <- cond -< x if b then returnA -< () else do From git at git.haskell.org Mon May 22 15:50:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 May 2017 15:50:14 +0000 (UTC) Subject: [commit: ghc] master: Ensure package.cache is newer than registration files after make install (d6686a2) Message-ID: <20170522155014.B1E4F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d6686a254293442a633482eae7ca78be968bef58/ghc >--------------------------------------------------------------- commit d6686a254293442a633482eae7ca78be968bef58 Author: Ben Gamari Date: Sun May 21 11:11:30 2017 -0400 Ensure package.cache is newer than registration files after make install Rebuild package.cache to ensure that it's newer than the package database registration files, avoiding out-of-date cache warnings from ghc-pkg. See #13375. Test Plan: `make install`, run `ghc-pkg list`, look for out-of-date cache warning Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #13375 Differential Revision: https://phabricator.haskell.org/D3569 >--------------------------------------------------------------- d6686a254293442a633482eae7ca78be968bef58 ghc.mk | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/ghc.mk b/ghc.mk index ce71a55..ea02191 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1027,6 +1027,10 @@ install_packages: rts/dist/package.conf.install # with an 077 umask. for f in '$(INSTALLED_PACKAGE_CONF)'/*; do $(CREATE_DATA) "$$f"; done +# Finally, update package.cache to ensure it's newer than the registration +# files. This avoids #13375. + $(INSTALLED_GHC_PKG_REAL) --global-package-db "$(INSTALLED_PACKAGE_CONF)" recache + # ----------------------------------------------------------------------------- # Binary distributions From git at git.haskell.org Mon May 22 16:41:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 May 2017 16:41:40 +0000 (UTC) Subject: [commit: ghc] master: fix a memory leak in osNumaMask (83ee930) Message-ID: <20170522164140.1E3903A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/83ee930fdd125d74939307ed3fa1bf6a2ba7fb36/ghc >--------------------------------------------------------------- commit 83ee930fdd125d74939307ed3fa1bf6a2ba7fb36 Author: Kubo Kovac Date: Mon May 22 11:51:55 2017 -0400 fix a memory leak in osNumaMask got an error when using asan: ``` ==1866689==ERROR: LeakSanitizer: detected memory leaks Direct leak of 16 byte(s) in 1 object(s) allocated from: #0 0x10640568 in malloc ??:? #1 0x154d867e in numa_bitmask_alloc .../numactl-2.0.8/libnuma_nosymve r.c:204 #2 0x154d867e in numa_allocate_nodemask .../numactl-2.0.8/libnuma_nosymve r.c:724 #3 0x154d867e in numa_get_mems_allowed .../numactl-2.0.8/libnuma_nosymve r.c:1141 #4 0x10b54a45 in osNumaMask ...ghc-8.0.2/rts/posix/OSMem.c:59 8 ``` Test Plan: compile, validate Reviewers: simonmar, niteria, austin, bgamari, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3537 >--------------------------------------------------------------- 83ee930fdd125d74939307ed3fa1bf6a2ba7fb36 rts/posix/OSMem.c | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/rts/posix/OSMem.c b/rts/posix/OSMem.c index 330da21..6ccd65a 100644 --- a/rts/posix/OSMem.c +++ b/rts/posix/OSMem.c @@ -601,7 +601,9 @@ uint64_t osNumaMask(void) if (osNumaNodes() > sizeof(StgWord)*8) { barf("osNumaMask: too many NUMA nodes (%d)", osNumaNodes()); } - return mask->maskp[0]; + uint64_t r = mask->maskp[0]; + numa_bitmask_free(mask); + return r; #else return 1; #endif From git at git.haskell.org Mon May 22 16:41:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 May 2017 16:41:37 +0000 (UTC) Subject: [commit: ghc] master: Rewrite boot in Python (0440af6) Message-ID: <20170522164137.64A103A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0440af6abe592c2366d302d603664fe763ad0828/ghc >--------------------------------------------------------------- commit 0440af6abe592c2366d302d603664fe763ad0828 Author: Ben Gamari Date: Mon May 22 11:50:55 2017 -0400 Rewrite boot in Python Test Plan: Validate Reviewers: hvr, austin Subscribers: rwbarton, thomie, erikd Differential Revision: https://phabricator.haskell.org/D3567 >--------------------------------------------------------------- 0440af6abe592c2366d302d603664fe763ad0828 INSTALL.md | 8 +- MAKEHELP.md | 2 +- boot | 385 ++++++++++++++++++++++++----------------------------------- configure.ac | 2 +- validate | 4 +- 5 files changed, 165 insertions(+), 236 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 0440af6abe592c2366d302d603664fe763ad0828 From git at git.haskell.org Mon May 22 16:41:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 May 2017 16:41:49 +0000 (UTC) Subject: [commit: ghc] master: Handle file targets in missing home modules warning (dac49bd) Message-ID: <20170522164149.54A593A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dac49bdc79387ca9f91c7c5c9220699efb6239fb/ghc >--------------------------------------------------------------- commit dac49bdc79387ca9f91c7c5c9220699efb6239fb Author: Herbert Valerio Riedel Date: Mon May 22 11:59:56 2017 -0400 Handle file targets in missing home modules warning When main module is listed on command line as a file, we should not issue a warning about it. See Trac #13727 Reviewers: austin, bgamari, Yuras Reviewed By: bgamari, Yuras Subscribers: 23Skidoo, rwbarton, thomie GHC Trac Issues: #13727 Differential Revision: https://phabricator.haskell.org/D3598 >--------------------------------------------------------------- dac49bdc79387ca9f91c7c5c9220699efb6239fb compiler/main/GhcMake.hs | 38 ++++++++++++++++------ .../should_compile/T13727}/Makefile | 0 .../warnings/should_compile/T13727/T13727a.stderr | 6 ++++ .../warnings/should_compile/T13727/T13727b.stderr | 6 ++++ .../warnings/should_compile/T13727/T13727c.stderr | 3 ++ .../warnings/should_compile/T13727/T13727d.stderr | 3 ++ .../warnings/should_compile/T13727/T13727e.stderr | 3 ++ .../warnings/should_compile/T13727/T13727f.stderr | 7 ++++ .../warnings/should_compile/T13727/T13727g.stderr | 7 ++++ .../warnings/should_compile/T13727/T13727h.stderr | 7 ++++ .../warnings/should_compile/T13727/T13727i.stderr | 7 ++++ .../warnings/should_compile/T13727/T13727j.stderr | 7 ++++ .../warnings/should_compile/T13727/T13727k.stderr | 4 +++ .../tests/warnings/should_compile/T13727/all.T | 20 ++++++++++++ .../should_compile/T13727/src-exe/AltMain.hs | 6 ++++ .../warnings/should_compile/T13727/src-exe/Main.hs | 6 ++++ .../warnings/should_compile/T13727/src-lib/M1.hs | 1 + 17 files changed, 121 insertions(+), 10 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 dac49bdc79387ca9f91c7c5c9220699efb6239fb From git at git.haskell.org Mon May 22 16:41:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 May 2017 16:41:42 +0000 (UTC) Subject: [commit: ghc] master: Add "header" to GHC_COLORS (139ef04) Message-ID: <20170522164142.CB0973A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/139ef04bdbd14b74dd6202295e11a37295442fc8/ghc >--------------------------------------------------------------- commit 139ef04bdbd14b74dd6202295e11a37295442fc8 Author: Phil Ruffwind Date: Mon May 22 12:00:34 2017 -0400 Add "header" to GHC_COLORS Add "header" to GHC_COLORS and allow colors to be inherited from the surroundings. Test Plan: validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13718 Differential Revision: https://phabricator.haskell.org/D3599 >--------------------------------------------------------------- 139ef04bdbd14b74dd6202295e11a37295442fc8 compiler/main/ErrUtils.hs | 6 ++++-- compiler/utils/Outputable.hs | 11 +++++------ compiler/utils/PprColour.hs | 17 ++++++++++++----- docs/users_guide/using.rst | 22 +++++++++++++++++++--- 4 files changed, 40 insertions(+), 16 deletions(-) diff --git a/compiler/main/ErrUtils.hs b/compiler/main/ErrUtils.hs index b0bbe3c..40f6648 100644 --- a/compiler/main/ErrUtils.hs +++ b/compiler/main/ErrUtils.hs @@ -209,10 +209,12 @@ mkLocMessageAnn ann severity locn msg -- Add prefixes, like Foo.hs:34: warning: -- - prefix = locn' <> colon <+> + header = locn' <> colon <+> coloured sevColour sevText <> optAnn - in coloured (Col.sMessage (colScheme dflags)) (hang prefix 4 msg) + in coloured (Col.sMessage (colScheme dflags)) + (hang (coloured (Col.sHeader (colScheme dflags)) header) 4 + msg) where sevText = diff --git a/compiler/utils/Outputable.hs b/compiler/utils/Outputable.hs index 403c5ce..4107e5b 100644 --- a/compiler/utils/Outputable.hs +++ b/compiler/utils/Outputable.hs @@ -723,19 +723,18 @@ ppUnless False doc = doc -- -- Only takes effect if colours are enabled. coloured :: Col.PprColour -> SDoc -> SDoc -coloured col@(Col.PprColour c) sdoc = +coloured col sdoc = sdocWithDynFlags $ \dflags -> if shouldUseColor dflags - then SDoc $ \ctx at SDC{ sdocLastColour = Col.PprColour lc } -> + then SDoc $ \ctx at SDC{ sdocLastColour = lastCol } -> case ctx of SDC{ sdocStyle = PprUser _ _ Coloured } -> - let ctx' = ctx{ sdocLastColour = col } in - Pretty.zeroWidthText (cReset ++ c) + let ctx' = ctx{ sdocLastColour = lastCol `mappend` col } in + Pretty.zeroWidthText (Col.renderColour col) Pretty.<> runSDoc sdoc ctx' - Pretty.<> Pretty.zeroWidthText (cReset ++ lc) + Pretty.<> Pretty.zeroWidthText (Col.renderColourAfresh lastCol) _ -> runSDoc sdoc ctx else sdoc - where Col.PprColour cReset = Col.colReset keyword :: SDoc -> SDoc keyword = coloured Col.colBold diff --git a/compiler/utils/PprColour.hs b/compiler/utils/PprColour.hs index 1b97303..ba7435d 100644 --- a/compiler/utils/PprColour.hs +++ b/compiler/utils/PprColour.hs @@ -3,7 +3,7 @@ import Data.Maybe (fromMaybe) import Util (OverridingBool(..), split) -- | A colour\/style for use with 'coloured'. -newtype PprColour = PprColour String +newtype PprColour = PprColour { renderColour :: String } -- | Allow colours to be combined (e.g. bold + red); -- In case of conflict, right side takes precedence. @@ -11,8 +11,12 @@ instance Monoid PprColour where mempty = PprColour mempty PprColour s1 `mappend` PprColour s2 = PprColour (s1 `mappend` s2) +renderColourAfresh :: PprColour -> String +renderColourAfresh c = renderColour (colReset `mappend` c) + colCustom :: String -> PprColour -colCustom s = PprColour ("\27[" ++ s ++ "m") +colCustom "" = mempty +colCustom s = PprColour ("\27[" ++ s ++ "m") colReset :: PprColour colReset = colCustom "0" @@ -46,7 +50,8 @@ colWhiteFg = colCustom "37" data Scheme = Scheme - { sMessage :: PprColour + { sHeader :: PprColour + , sMessage :: PprColour , sWarning :: PprColour , sError :: PprColour , sFatal :: PprColour @@ -56,7 +61,8 @@ data Scheme = defaultScheme :: Scheme defaultScheme = Scheme - { sMessage = colBold + { sHeader = mempty + , sMessage = colBold , sWarning = colBold `mappend` colMagentaFg , sError = colBold `mappend` colRedFg , sFatal = colBold `mappend` colRedFg @@ -72,7 +78,8 @@ parseScheme "never" (_, cs) = (Never, cs) parseScheme input (b, cs) = ( b , Scheme - { sMessage = fromMaybe (sMessage cs) (lookup "message" table) + { sHeader = fromMaybe (sHeader cs) (lookup "header" table) + , sMessage = fromMaybe (sMessage cs) (lookup "message" table) , sWarning = fromMaybe (sWarning cs) (lookup "warning" table) , sError = fromMaybe (sError cs) (lookup "error" table) , sFatal = fromMaybe (sFatal cs) (lookup "fatal" table) diff --git a/docs/users_guide/using.rst b/docs/users_guide/using.rst index fc19dfd..84dae9f 100644 --- a/docs/users_guide/using.rst +++ b/docs/users_guide/using.rst @@ -804,14 +804,30 @@ messages and in GHCi: .. code-block:: none - message=1:warning=1;35:error=1;31:fatal=1;31:margin=1;34 + header=:message=1:warning=1;35:error=1;31:fatal=1;31:margin=1;34 Each value is expected to be a `Select Graphic Rendition (SGR) substring - `_. + `_. The + formatting of each element can inherit from parent elements. For example, + if ``header`` is left empty, it will inherit the formatting of + ``message``. Alternatively if ``header`` is set to ``1`` (bold), it will + be bolded but still inherits the color of ``message``. + + Currently, in the primary message, the following inheritance tree is in + place: + + - ``message`` + - ``header`` + - ``warning`` + - ``error`` + - ``fatal`` + + In the caret diagnostics, there is currently no inheritance at all between + ``margin``, ``warning``, ``error``, and ``fatal``. The environment variable can also be set to the magical values ``never`` or ``always``, which is equivalent to setting the corresponding - ``-fdiagnostics-color`` flag but has lower precedence. + ``-fdiagnostics-color`` flag but with lower precedence. .. ghc-flag:: -f[no-]diagnostics-show-caret From git at git.haskell.org Mon May 22 16:41:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 May 2017 16:41:46 +0000 (UTC) Subject: [commit: ghc] master: Testcase for type family consistency checks (2bc3a05) Message-ID: <20170522164146.80CE53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2bc3a0570dac333cc7fb6f8038e08f36d62e4d13/ghc >--------------------------------------------------------------- commit 2bc3a0570dac333cc7fb6f8038e08f36d62e4d13 Author: Bartosz Nitka Date: Mon May 22 12:01:05 2017 -0400 Testcase for type family consistency checks Based on my quick search, we don't have a test that verifies that we check the type family instances of currently compiled module against direct or indirect dependencies. This adds two tests: for a direct dependency and for an indirect dependency. I also added a comment to make it clear what the 'Over' test tests. Other than completeness, it makes sense to have these tests because if you look at Note [The type family instance consistency story] in FamInsts these cases are checked through different mechanisms. Test Plan: new tests Reviewers: simonmar, rwbarton, simonpj, austin, bgamari Reviewed By: simonpj, bgamari Subscribers: thomie GHC Trac Issues: #13719 Differential Revision: https://phabricator.haskell.org/D3602 >--------------------------------------------------------------- 2bc3a0570dac333cc7fb6f8038e08f36d62e4d13 testsuite/tests/indexed-types/should_fail/OverD.hs | 2 ++ .../indexed-types/should_fail/OverDirectThisMod.stderr | 10 ++++++++++ .../should_fail/{OverA.hs => OverDirectThisModA.hs} | 2 +- .../tests/indexed-types/should_fail/OverDirectThisModB.hs | 9 +++++++++ .../tests/indexed-types/should_fail/OverDirectThisModC.hs | 12 ++++++++++++ .../indexed-types/should_fail/OverIndirectThisMod.stderr | 12 ++++++++++++ .../should_fail/{OverA.hs => OverIndirectThisModA.hs} | 2 +- .../tests/indexed-types/should_fail/OverIndirectThisModB.hs | 9 +++++++++ .../tests/indexed-types/should_fail/OverIndirectThisModC.hs | 2 ++ .../tests/indexed-types/should_fail/OverIndirectThisModD.hs | 13 +++++++++++++ testsuite/tests/indexed-types/should_fail/all.T | 2 ++ 11 files changed, 73 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/indexed-types/should_fail/OverD.hs b/testsuite/tests/indexed-types/should_fail/OverD.hs index 3bce8de..ec57974 100644 --- a/testsuite/tests/indexed-types/should_fail/OverD.hs +++ b/testsuite/tests/indexed-types/should_fail/OverD.hs @@ -1,3 +1,5 @@ module OverD where +-- Tests that we verify consistency of type families between +-- transitive imports. import OverB import OverC diff --git a/testsuite/tests/indexed-types/should_fail/OverDirectThisMod.stderr b/testsuite/tests/indexed-types/should_fail/OverDirectThisMod.stderr new file mode 100644 index 0000000..28c72df --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/OverDirectThisMod.stderr @@ -0,0 +1,10 @@ + +OverDirectThisModB.hs:7:15: error: + Conflicting family instance declarations: + C [Int] [a] = CListList2 -- Defined at OverDirectThisModB.hs:7:15 + C [a] [Int] = C9ListList -- Defined at OverDirectThisModC.hs:10:15 + +OverDirectThisModB.hs:9:15: error: + Conflicting family instance declarations: + D [Int] [a] = Int -- Defined at OverDirectThisModB.hs:9:15 + D [a] [Int] = Char -- Defined at OverDirectThisModC.hs:12:15 diff --git a/testsuite/tests/indexed-types/should_fail/OverA.hs b/testsuite/tests/indexed-types/should_fail/OverDirectThisModA.hs similarity index 52% copy from testsuite/tests/indexed-types/should_fail/OverA.hs copy to testsuite/tests/indexed-types/should_fail/OverDirectThisModA.hs index 0f05737..d2655b6 100644 --- a/testsuite/tests/indexed-types/should_fail/OverA.hs +++ b/testsuite/tests/indexed-types/should_fail/OverDirectThisModA.hs @@ -1,6 +1,6 @@ {-# LANGUAGE TypeFamilies #-} -module OverA (C, D) +module OverDirectThisModA (C, D) where data family C a b :: * diff --git a/testsuite/tests/indexed-types/should_fail/OverDirectThisModB.hs b/testsuite/tests/indexed-types/should_fail/OverDirectThisModB.hs new file mode 100644 index 0000000..4215edf --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/OverDirectThisModB.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE TypeFamilies #-} + +module OverDirectThisModB +where +import OverDirectThisModA (C, D) + +data instance C [Int] [a] = CListList2 + +type instance D [Int] [a] = Int diff --git a/testsuite/tests/indexed-types/should_fail/OverDirectThisModC.hs b/testsuite/tests/indexed-types/should_fail/OverDirectThisModC.hs new file mode 100644 index 0000000..aa0f888 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/OverDirectThisModC.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE TypeFamilies #-} +-- Tests that we check family instance consistency between +-- type family instances defined in the currently compiled module +-- and the direct imports. +module OverDirectThisModC +where +import OverDirectThisModB +import OverDirectThisModA (C, D) + +data instance C [a] [Int] = C9ListList + +type instance D [a] [Int] = Char diff --git a/testsuite/tests/indexed-types/should_fail/OverIndirectThisMod.stderr b/testsuite/tests/indexed-types/should_fail/OverIndirectThisMod.stderr new file mode 100644 index 0000000..53c93e8 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/OverIndirectThisMod.stderr @@ -0,0 +1,12 @@ + +OverIndirectThisModB.hs:7:15: error: + Conflicting family instance declarations: + C [Int] [a] = OverIndirectThisModB.CListList2 + -- Defined at OverIndirectThisModB.hs:7:15 + C [a] [Int] = C9ListList + -- Defined at OverIndirectThisModD.hs:11:15 + +OverIndirectThisModB.hs:9:15: error: + Conflicting family instance declarations: + D [Int] [a] = Int -- Defined at OverIndirectThisModB.hs:9:15 + D [a] [Int] = Char -- Defined at OverIndirectThisModD.hs:13:15 diff --git a/testsuite/tests/indexed-types/should_fail/OverA.hs b/testsuite/tests/indexed-types/should_fail/OverIndirectThisModA.hs similarity index 51% copy from testsuite/tests/indexed-types/should_fail/OverA.hs copy to testsuite/tests/indexed-types/should_fail/OverIndirectThisModA.hs index 0f05737..f316ac1 100644 --- a/testsuite/tests/indexed-types/should_fail/OverA.hs +++ b/testsuite/tests/indexed-types/should_fail/OverIndirectThisModA.hs @@ -1,6 +1,6 @@ {-# LANGUAGE TypeFamilies #-} -module OverA (C, D) +module OverIndirectThisModA (C, D) where data family C a b :: * diff --git a/testsuite/tests/indexed-types/should_fail/OverIndirectThisModB.hs b/testsuite/tests/indexed-types/should_fail/OverIndirectThisModB.hs new file mode 100644 index 0000000..ed152d5 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/OverIndirectThisModB.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE TypeFamilies #-} + +module OverIndirectThisModB +where +import OverIndirectThisModA (C, D) + +data instance C [Int] [a] = CListList2 + +type instance D [Int] [a] = Int diff --git a/testsuite/tests/indexed-types/should_fail/OverIndirectThisModC.hs b/testsuite/tests/indexed-types/should_fail/OverIndirectThisModC.hs new file mode 100644 index 0000000..e39a27d --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/OverIndirectThisModC.hs @@ -0,0 +1,2 @@ +module OverIndirectThisModC where +import OverIndirectThisModB diff --git a/testsuite/tests/indexed-types/should_fail/OverIndirectThisModD.hs b/testsuite/tests/indexed-types/should_fail/OverIndirectThisModD.hs new file mode 100644 index 0000000..a75007b --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/OverIndirectThisModD.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE TypeFamilies #-} +-- Tests that we check family instance consistency between +-- type family instances defined in the currently compiled module +-- and the transitive imports. +module OverIndirectThisModD +where +import OverIndirectThisModC + -- imports OverIndirectThisModB with conflicting instances +import OverIndirectThisModA (C, D) + +data instance C [a] [Int] = C9ListList + +type instance D [a] [Int] = Char diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index cca1e8d..9cad8e1 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -30,6 +30,8 @@ test('NonLinearSigErr', normal, compile, ['']) test('GADTwrong1', normal, compile_fail, ['']) test('Over', [], multimod_compile_fail, ['OverD', '-no-hs-main -c -v0']) +test('OverDirectThisMod', [], multimod_compile_fail, ['OverDirectThisModC', '-no-hs-main -c -v0']) +test('OverIndirectThisMod', [], multimod_compile_fail, ['OverIndirectThisModD', '-no-hs-main -c -v0']) test('SkolemOccursLoop', expect_fail, compile_fail, ['']) From git at git.haskell.org Mon May 22 16:41:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 May 2017 16:41:52 +0000 (UTC) Subject: [commit: ghc] master: Testcase for #13719 (17fef39) Message-ID: <20170522164152.5D5F03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/17fef390c575c153c7e70438783e7f8fee62e451/ghc >--------------------------------------------------------------- commit 17fef390c575c153c7e70438783e7f8fee62e451 Author: Bartosz Nitka Date: Mon May 22 12:00:52 2017 -0400 Testcase for #13719 I expect to improve this, a testcase will ensure it doesn't regress. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13719 Differential Revision: https://phabricator.haskell.org/D3600 >--------------------------------------------------------------- 17fef390c575c153c7e70438783e7f8fee62e451 testsuite/tests/perf/compiler/all.T | 11 +++++++++++ testsuite/tests/perf/compiler/genT13719 | 31 +++++++++++++++++++++++++++++++ 2 files changed, 42 insertions(+) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index c90378b..17da229 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -1108,3 +1108,14 @@ test('MultiLayerModules', ], multimod_compile, ['MultiLayerModules', '-v0']) + +test('T13719', + [ compiler_stats_num_field('bytes allocated', + [(wordsize(64), 49907410784, 10), + # initial: 49907410784 + ]), + pre_cmd('./genT13719'), + extra_files(['genT13719']), + ], + multimod_compile, + ['T13719', '-v0']) diff --git a/testsuite/tests/perf/compiler/genT13719 b/testsuite/tests/perf/compiler/genT13719 new file mode 100755 index 0000000..ccc078e --- /dev/null +++ b/testsuite/tests/perf/compiler/genT13719 @@ -0,0 +1,31 @@ +#!/bin/bash +# Generate $DEPTH layers of modules with $WIDTH modules on each layer +# Every module on layer N imports all the modules on layer N-1 +# $ROOT.hs imports all the modules from the last layer +# Every module defines a datatype that derives Generic. +# The derived Generic defines one 'Rep' type family instance. +DEPTH=2 +WIDTH=100 +ROOT=T13719 +for i in $(seq -w 1 $WIDTH); do + l=0 + echo "{-# LANGUAGE DeriveGeneric #-}" > DummyLevel${l}M$i.hs; + echo "module DummyLevel${l}M$i where" >> DummyLevel${l}M$i.hs; + echo "import GHC.Generics" >> DummyLevel${l}M$i.hs; + echo "data DummyLevel${l}M${i}G = DummyLevel${l}M${i}G deriving Generic" >> DummyLevel${l}M$i.hs; +done +for l in $(seq 1 $DEPTH); do + for i in $(seq -w 1 $WIDTH); do + echo "{-# LANGUAGE DeriveGeneric #-}" > DummyLevel${l}M$i.hs; + echo "module DummyLevel${l}M$i where" >> DummyLevel${l}M$i.hs; + echo "import GHC.Generics" >> DummyLevel${l}M$i.hs; + for j in $(seq -w 1 $WIDTH); do + echo "import DummyLevel$((l-1))M$j" >> DummyLevel${l}M$i.hs; + done + echo "data DummyLevel${l}M${i}G = DummyLevel${l}M${i}G deriving Generic" >> DummyLevel${l}M$i.hs; + done +done +echo "module ${ROOT} where" > $ROOT.hs +for j in $(seq -w 1 $WIDTH); do + echo "import DummyLevel${DEPTH}M$j" >> $ROOT.hs; +done From git at git.haskell.org Mon May 22 17:17:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 May 2017 17:17:02 +0000 (UTC) Subject: [commit: ghc] master: Extend ModuleSet with useful functions (033f897) Message-ID: <20170522171702.974973A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/033f897a8ad34d62aff585d9df16c640bb55f21c/ghc >--------------------------------------------------------------- commit 033f897a8ad34d62aff585d9df16c640bb55f21c Author: Bartosz Nitka Date: Mon May 22 10:16:26 2017 -0700 Extend ModuleSet with useful functions >--------------------------------------------------------------- 033f897a8ad34d62aff585d9df16c640bb55f21c compiler/basicTypes/Module.hs | 20 +++++++++++++++++++- 1 file changed, 19 insertions(+), 1 deletion(-) diff --git a/compiler/basicTypes/Module.hs b/compiler/basicTypes/Module.hs index 4a3212f..c693e7a 100644 --- a/compiler/basicTypes/Module.hs +++ b/compiler/basicTypes/Module.hs @@ -131,7 +131,10 @@ module Module -- * Sets of Modules ModuleSet, - emptyModuleSet, mkModuleSet, moduleSetElts, extendModuleSet, elemModuleSet + emptyModuleSet, mkModuleSet, moduleSetElts, + extendModuleSet, extendModuleSetList, + elemModuleSet, intersectModuleSet, minusModuleSet, unionModuleSet, + unitModuleSet ) where import Config @@ -1255,6 +1258,9 @@ mkModuleSet = Set.fromList . coerce extendModuleSet :: ModuleSet -> Module -> ModuleSet extendModuleSet s m = Set.insert (NDModule m) s +extendModuleSetList :: ModuleSet -> [Module] -> ModuleSet +extendModuleSetList s ms = foldl' (coerce . flip Set.insert) s ms + emptyModuleSet :: ModuleSet emptyModuleSet = Set.empty @@ -1264,6 +1270,18 @@ moduleSetElts = sort . coerce . Set.toList elemModuleSet :: Module -> ModuleSet -> Bool elemModuleSet = Set.member . coerce +intersectModuleSet :: ModuleSet -> ModuleSet -> ModuleSet +intersectModuleSet = coerce Set.intersection + +minusModuleSet :: ModuleSet -> ModuleSet -> ModuleSet +minusModuleSet = coerce Set.difference + +unionModuleSet :: ModuleSet -> ModuleSet -> ModuleSet +unionModuleSet = coerce Set.union + +unitModuleSet :: Module -> ModuleSet +unitModuleSet = coerce Set.singleton + {- A ModuleName has a Unique, so we can build mappings of these using UniqFM. From git at git.haskell.org Mon May 22 19:21:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 May 2017 19:21:27 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Ensure package.cache is newer than registration files after make install (4ea0868) Message-ID: <20170522192127.B4E573A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/4ea0868737cfce7051bc10a731d5de152c93fde5/ghc >--------------------------------------------------------------- commit 4ea0868737cfce7051bc10a731d5de152c93fde5 Author: Ben Gamari Date: Sun May 21 11:11:30 2017 -0400 Ensure package.cache is newer than registration files after make install Rebuild package.cache to ensure that it's newer than the package database registration files, avoiding out-of-date cache warnings from ghc-pkg. See #13375. Test Plan: `make install`, run `ghc-pkg list`, look for out-of-date cache warning Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #13375 Differential Revision: https://phabricator.haskell.org/D3569 (cherry picked from commit d6686a254293442a633482eae7ca78be968bef58) >--------------------------------------------------------------- 4ea0868737cfce7051bc10a731d5de152c93fde5 ghc.mk | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/ghc.mk b/ghc.mk index ca2aa95..004ac4a 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1018,6 +1018,10 @@ install_packages: rts/dist/package.conf.install # with an 077 umask. for f in '$(INSTALLED_PACKAGE_CONF)'/*; do $(CREATE_DATA) "$$f"; done +# Finally, update package.cache to ensure it's newer than the registration +# files. This avoids #13375. + $(INSTALLED_GHC_PKG_REAL) --global-package-db "$(INSTALLED_PACKAGE_CONF)" recache + # ----------------------------------------------------------------------------- # Binary distributions From git at git.haskell.org Mon May 22 19:21:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 May 2017 19:21:30 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: fix a memory leak in osNumaMask (2a5f7b3) Message-ID: <20170522192130.6E7013A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/2a5f7b3c1e1e75aedac76f7de40d2b6410928356/ghc >--------------------------------------------------------------- commit 2a5f7b3c1e1e75aedac76f7de40d2b6410928356 Author: Kubo Kovac Date: Mon May 22 11:51:55 2017 -0400 fix a memory leak in osNumaMask got an error when using asan: ``` ==1866689==ERROR: LeakSanitizer: detected memory leaks Direct leak of 16 byte(s) in 1 object(s) allocated from: #0 0x10640568 in malloc ??:? #1 0x154d867e in numa_bitmask_alloc .../numactl-2.0.8/libnuma_nosymve r.c:204 #2 0x154d867e in numa_allocate_nodemask .../numactl-2.0.8/libnuma_nosymve r.c:724 #3 0x154d867e in numa_get_mems_allowed .../numactl-2.0.8/libnuma_nosymve r.c:1141 #4 0x10b54a45 in osNumaMask ...ghc-8.0.2/rts/posix/OSMem.c:59 8 ``` Test Plan: compile, validate Reviewers: simonmar, niteria, austin, bgamari, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3537 (cherry picked from commit 83ee930fdd125d74939307ed3fa1bf6a2ba7fb36) >--------------------------------------------------------------- 2a5f7b3c1e1e75aedac76f7de40d2b6410928356 rts/posix/OSMem.c | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/rts/posix/OSMem.c b/rts/posix/OSMem.c index dcf734f..e2aa288 100644 --- a/rts/posix/OSMem.c +++ b/rts/posix/OSMem.c @@ -601,7 +601,9 @@ uint64_t osNumaMask(void) if (osNumaNodes() > sizeof(StgWord)*8) { barf("osNumaMask: too many NUMA nodes (%d)", osNumaNodes()); } - return mask->maskp[0]; + uint64_t r = mask->maskp[0]; + numa_bitmask_free(mask); + return r; #else return 1; #endif From git at git.haskell.org Mon May 22 19:21:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 May 2017 19:21:33 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Add "header" to GHC_COLORS (c0b82c3) Message-ID: <20170522192133.30F583A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/c0b82c3826c8e1b26d198f050baa9d5077370247/ghc >--------------------------------------------------------------- commit c0b82c3826c8e1b26d198f050baa9d5077370247 Author: Phil Ruffwind Date: Mon May 22 12:00:34 2017 -0400 Add "header" to GHC_COLORS Add "header" to GHC_COLORS and allow colors to be inherited from the surroundings. Test Plan: validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13718 Differential Revision: https://phabricator.haskell.org/D3599 (cherry picked from commit 139ef04bdbd14b74dd6202295e11a37295442fc8) >--------------------------------------------------------------- c0b82c3826c8e1b26d198f050baa9d5077370247 compiler/main/ErrUtils.hs | 6 ++++-- compiler/utils/Outputable.hs | 11 +++++------ compiler/utils/PprColour.hs | 17 ++++++++++++----- docs/users_guide/using.rst | 22 +++++++++++++++++++--- 4 files changed, 40 insertions(+), 16 deletions(-) diff --git a/compiler/main/ErrUtils.hs b/compiler/main/ErrUtils.hs index b0bbe3c..40f6648 100644 --- a/compiler/main/ErrUtils.hs +++ b/compiler/main/ErrUtils.hs @@ -209,10 +209,12 @@ mkLocMessageAnn ann severity locn msg -- Add prefixes, like Foo.hs:34: warning: -- - prefix = locn' <> colon <+> + header = locn' <> colon <+> coloured sevColour sevText <> optAnn - in coloured (Col.sMessage (colScheme dflags)) (hang prefix 4 msg) + in coloured (Col.sMessage (colScheme dflags)) + (hang (coloured (Col.sHeader (colScheme dflags)) header) 4 + msg) where sevText = diff --git a/compiler/utils/Outputable.hs b/compiler/utils/Outputable.hs index 403c5ce..4107e5b 100644 --- a/compiler/utils/Outputable.hs +++ b/compiler/utils/Outputable.hs @@ -723,19 +723,18 @@ ppUnless False doc = doc -- -- Only takes effect if colours are enabled. coloured :: Col.PprColour -> SDoc -> SDoc -coloured col@(Col.PprColour c) sdoc = +coloured col sdoc = sdocWithDynFlags $ \dflags -> if shouldUseColor dflags - then SDoc $ \ctx at SDC{ sdocLastColour = Col.PprColour lc } -> + then SDoc $ \ctx at SDC{ sdocLastColour = lastCol } -> case ctx of SDC{ sdocStyle = PprUser _ _ Coloured } -> - let ctx' = ctx{ sdocLastColour = col } in - Pretty.zeroWidthText (cReset ++ c) + let ctx' = ctx{ sdocLastColour = lastCol `mappend` col } in + Pretty.zeroWidthText (Col.renderColour col) Pretty.<> runSDoc sdoc ctx' - Pretty.<> Pretty.zeroWidthText (cReset ++ lc) + Pretty.<> Pretty.zeroWidthText (Col.renderColourAfresh lastCol) _ -> runSDoc sdoc ctx else sdoc - where Col.PprColour cReset = Col.colReset keyword :: SDoc -> SDoc keyword = coloured Col.colBold diff --git a/compiler/utils/PprColour.hs b/compiler/utils/PprColour.hs index 1b97303..ba7435d 100644 --- a/compiler/utils/PprColour.hs +++ b/compiler/utils/PprColour.hs @@ -3,7 +3,7 @@ import Data.Maybe (fromMaybe) import Util (OverridingBool(..), split) -- | A colour\/style for use with 'coloured'. -newtype PprColour = PprColour String +newtype PprColour = PprColour { renderColour :: String } -- | Allow colours to be combined (e.g. bold + red); -- In case of conflict, right side takes precedence. @@ -11,8 +11,12 @@ instance Monoid PprColour where mempty = PprColour mempty PprColour s1 `mappend` PprColour s2 = PprColour (s1 `mappend` s2) +renderColourAfresh :: PprColour -> String +renderColourAfresh c = renderColour (colReset `mappend` c) + colCustom :: String -> PprColour -colCustom s = PprColour ("\27[" ++ s ++ "m") +colCustom "" = mempty +colCustom s = PprColour ("\27[" ++ s ++ "m") colReset :: PprColour colReset = colCustom "0" @@ -46,7 +50,8 @@ colWhiteFg = colCustom "37" data Scheme = Scheme - { sMessage :: PprColour + { sHeader :: PprColour + , sMessage :: PprColour , sWarning :: PprColour , sError :: PprColour , sFatal :: PprColour @@ -56,7 +61,8 @@ data Scheme = defaultScheme :: Scheme defaultScheme = Scheme - { sMessage = colBold + { sHeader = mempty + , sMessage = colBold , sWarning = colBold `mappend` colMagentaFg , sError = colBold `mappend` colRedFg , sFatal = colBold `mappend` colRedFg @@ -72,7 +78,8 @@ parseScheme "never" (_, cs) = (Never, cs) parseScheme input (b, cs) = ( b , Scheme - { sMessage = fromMaybe (sMessage cs) (lookup "message" table) + { sHeader = fromMaybe (sHeader cs) (lookup "header" table) + , sMessage = fromMaybe (sMessage cs) (lookup "message" table) , sWarning = fromMaybe (sWarning cs) (lookup "warning" table) , sError = fromMaybe (sError cs) (lookup "error" table) , sFatal = fromMaybe (sFatal cs) (lookup "fatal" table) diff --git a/docs/users_guide/using.rst b/docs/users_guide/using.rst index fc19dfd..84dae9f 100644 --- a/docs/users_guide/using.rst +++ b/docs/users_guide/using.rst @@ -804,14 +804,30 @@ messages and in GHCi: .. code-block:: none - message=1:warning=1;35:error=1;31:fatal=1;31:margin=1;34 + header=:message=1:warning=1;35:error=1;31:fatal=1;31:margin=1;34 Each value is expected to be a `Select Graphic Rendition (SGR) substring - `_. + `_. The + formatting of each element can inherit from parent elements. For example, + if ``header`` is left empty, it will inherit the formatting of + ``message``. Alternatively if ``header`` is set to ``1`` (bold), it will + be bolded but still inherits the color of ``message``. + + Currently, in the primary message, the following inheritance tree is in + place: + + - ``message`` + - ``header`` + - ``warning`` + - ``error`` + - ``fatal`` + + In the caret diagnostics, there is currently no inheritance at all between + ``margin``, ``warning``, ``error``, and ``fatal``. The environment variable can also be set to the magical values ``never`` or ``always``, which is equivalent to setting the corresponding - ``-fdiagnostics-color`` flag but has lower precedence. + ``-fdiagnostics-color`` flag but with lower precedence. .. ghc-flag:: -f[no-]diagnostics-show-caret From git at git.haskell.org Mon May 22 19:21:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 May 2017 19:21:36 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Handle file targets in missing home modules warning (72eade6) Message-ID: <20170522192136.013213A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/72eade6d7cf47f0738a58f560085acc952248d2c/ghc >--------------------------------------------------------------- commit 72eade6d7cf47f0738a58f560085acc952248d2c Author: Herbert Valerio Riedel Date: Mon May 22 11:59:56 2017 -0400 Handle file targets in missing home modules warning When main module is listed on command line as a file, we should not issue a warning about it. See Trac #13727 Reviewers: austin, bgamari, Yuras Reviewed By: bgamari, Yuras Subscribers: 23Skidoo, rwbarton, thomie GHC Trac Issues: #13727 Differential Revision: https://phabricator.haskell.org/D3598 (cherry picked from commit dac49bdc79387ca9f91c7c5c9220699efb6239fb) >--------------------------------------------------------------- 72eade6d7cf47f0738a58f560085acc952248d2c compiler/main/GhcMake.hs | 38 ++++++++++++++++------ .../should_compile/T13727}/Makefile | 0 .../warnings/should_compile/T13727/T13727a.stderr | 6 ++++ .../warnings/should_compile/T13727/T13727b.stderr | 6 ++++ .../warnings/should_compile/T13727/T13727c.stderr | 3 ++ .../warnings/should_compile/T13727/T13727d.stderr | 3 ++ .../warnings/should_compile/T13727/T13727e.stderr | 3 ++ .../warnings/should_compile/T13727/T13727f.stderr | 7 ++++ .../warnings/should_compile/T13727/T13727g.stderr | 7 ++++ .../warnings/should_compile/T13727/T13727h.stderr | 7 ++++ .../warnings/should_compile/T13727/T13727i.stderr | 7 ++++ .../warnings/should_compile/T13727/T13727j.stderr | 7 ++++ .../warnings/should_compile/T13727/T13727k.stderr | 4 +++ .../tests/warnings/should_compile/T13727/all.T | 20 ++++++++++++ .../should_compile/T13727/src-exe/AltMain.hs | 6 ++++ .../warnings/should_compile/T13727/src-exe/Main.hs | 6 ++++ .../warnings/should_compile/T13727/src-lib/M1.hs | 1 + 17 files changed, 121 insertions(+), 10 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 72eade6d7cf47f0738a58f560085acc952248d2c From git at git.haskell.org Tue May 23 09:31:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 May 2017 09:31:37 +0000 (UTC) Subject: [commit: ghc] master: aclocal.m4: allow override of dllwrap and windres when cross-compiling (1fd06de) Message-ID: <20170523093137.73C2E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1fd06de4e98d1b659500ecd66d88d6d80fcc60d3/ghc >--------------------------------------------------------------- commit 1fd06de4e98d1b659500ecd66d88d6d80fcc60d3 Author: Sergei Trofimovich Date: Tue May 23 09:13:43 2017 +0100 aclocal.m4: allow override of dllwrap and windres when cross-compiling Commit 66108864540601837ad77847f4062a670362361f reverted ability to override 'dllwrap' and 'windres' paths when cross-compiling. After this change (and a few libraries/Win32 patches) I was able to build cross-compiler to windows: $ ./configure --target=i686-w64-mingw32 \ DllWrap=i686-w64-mingw32-dllwrap \ Windres=i686-w64-mingw32-windres Later both 'dllwrap' and 'windres' should be derived from --target= as we do now for 'CC', 'AR', 'NM' and others. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 1fd06de4e98d1b659500ecd66d88d6d80fcc60d3 aclocal.m4 | 14 ++++++++++++-- 1 file changed, 12 insertions(+), 2 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 697cba5..7ad9c36 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -479,8 +479,18 @@ AC_DEFUN([FP_SETTINGS], SettingsLdCommand="$LdCmd" SettingsArCommand="$ArCmd" SettingsPerlCommand="$PerlCmd" - SettingsDllWrapCommand="/bin/false" - SettingsWindresCommand="/bin/false" + if test -z "$DllWrap" + then + SettingsDllWrapCommand="/bin/false" + else + SettingsDllWrapCommand="$DllWrap" + fi + if test -z "$Windres" + then + SettingsWindresCommand="/bin/false" + else + SettingsWindresCommand="$Windres" + fi SettingsLibtoolCommand="libtool" SettingsTouchCommand='touch' fi From git at git.haskell.org Tue May 23 09:31:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 May 2017 09:31:40 +0000 (UTC) Subject: [commit: ghc] master: mk/config.mk.in: lower -O2 optimization down to -O1 on UNREG (432a1f1) Message-ID: <20170523093140.46F073A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/432a1f18327a50d7b2bbdbe6b004473fe1b0b0b9/ghc >--------------------------------------------------------------- commit 432a1f18327a50d7b2bbdbe6b004473fe1b0b0b9 Author: Sergei Trofimovich Date: Tue May 23 09:36:50 2017 +0100 mk/config.mk.in: lower -O2 optimization down to -O1 on UNREG It's not a new behaviour. First it was introduced by 2d5372cfdc2236a77ec49df249f3379b93224e06 ("lower -O2 optimization down to -O1 on UNREG") to fix build failure on unregisterised powerpc64. This time I've noticed build failures on unregisterised ia64. The change was accidentally reverted by commit 14d0f7f1221db758cd06a69f53803d9d0150164a ("Build system: Add stage specific SRC_HC_(WARNING_)OPTS) The revert happened due to the following code rearrangement: ifeq "$(GhcUnregisterised)" "YES" GhcStage1HcOpts= GhcStage2HcOpts= GhcStage3HcOpts= endif GhcUnregisterised=@Unregisterised@ As a result 'ifeq' part has no effect. The change moves 'ifeq' down to the very end of file and adds a note it depends on the 'GhcUnregisterised' variable. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 432a1f18327a50d7b2bbdbe6b004473fe1b0b0b9 mk/config.mk.in | 26 +++++++++++++++++--------- 1 file changed, 17 insertions(+), 9 deletions(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index 8901137..b2a9569 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -70,15 +70,6 @@ GhcStage1HcOpts= GhcStage2HcOpts=-O2 GhcStage3HcOpts=-O2 -# Disable -O2 optimization. Otherwise amount of generated C code -# makes things very slow to compile (~5 minutes on core-i7 for 'compiler/hsSyn/HsExpr.hs') -# and sometimes not compile at all (powerpc64 overflows something -# on 'compiler/hsSyn/HsExpr.hs'). -ifeq "$(GhcUnregisterised)" "YES" -GhcStage1HcOpts= -GhcStage2HcOpts= -GhcStage3HcOpts= -endif # Note [Stage number in build variables]. # @@ -901,3 +892,20 @@ GMP_LIB_DIRS = @GMP_LIB_DIRS@ CURSES_INCLUDE_DIRS = @CURSES_INCLUDE_DIRS@ CURSES_LIB_DIRS = @CURSES_LIB_DIRS@ + +# See Note [Disable -O2 in unregisteride mode] +# Be careful: 'GhcUnregisterised' should be defined earlier in this file. +ifeq "$(GhcUnregisterised)" "YES" +GhcStage1HcOpts= +GhcStage2HcOpts= +GhcStage3HcOpts= + +GhcLibHcOpts= +endif + +# Note [Disable -O2 in unregisteride mode] +# Disable -O2 optimization in uregisterised more. Otherwise amount +# of generated C code # makes things very slow to compile (~5 minutes +# on core-i7 for 'compiler/hsSyn/HsExpr.hs') and sometimes not compile +# at all: powerpc64 overflows TOC section on 'compiler/hsSyn/HsExpr.hs' +# ia64 overflows short data section on 'compiler/main/DynFlags.hs' From git at git.haskell.org Tue May 23 09:31:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 May 2017 09:31:43 +0000 (UTC) Subject: [commit: ghc] master: ghc.mk: rename installed ghc-stage1 on non-windows (1076010) Message-ID: <20170523093143.02B0D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/107601058b6189521c379f7ed7a2b0694792acbf/ghc >--------------------------------------------------------------- commit 107601058b6189521c379f7ed7a2b0694792acbf Author: Sergei Trofimovich Date: Tue May 23 09:45:50 2017 +0100 ghc.mk: rename installed ghc-stage1 on non-windows When user installs _native_ build ghc executable is renamed from '$(libexec)/bin/ghc-stage' to '$(libexec)/bin/ghc'. But not on windows! In case of _cross-compiler_ rename should happen only for '$(libexec)/bin/ghc-stage' runnable on non-windows platform. Before the change '$(libexec)/bin/ghc-stage' rename happened for any compiler not targeting windows. After the patch rename also happens for '$(libexec)/bin/ghc-stage1' cross-compiler built for linux targeting windows (Stage1Only=YES case). Or on a concrete example: # host is x86_64-pc-linux-gnu $ ./configure --target=i686-w64-mingw32 $ make install Stage1Only=YES Before the change the layout was: - '$(libexec)/bin/ghc-stage1' was installed - bin/ghc contained 'exec $(libexec)/bin/ghc' # missing file! After the change: - '$(libexec)/bin/ghc' was installed - bin/ghc contained 'exec $(libexec)/bin/ghc' # present file Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 107601058b6189521c379f7ed7a2b0694792acbf ghc.mk | 16 +++++++++++++--- 1 file changed, 13 insertions(+), 3 deletions(-) diff --git a/ghc.mk b/ghc.mk index ea02191..2272569 100644 --- a/ghc.mk +++ b/ghc.mk @@ -921,15 +921,25 @@ endif install_libs: $(INSTALL_LIBS) $(call installLibsTo, $(INSTALL_LIBS), "$(DESTDIR)$(ghclibdir)") +# We rename ghc-stage2, so that the right program name is used in error +# messages etc. But not on windows. +RENAME_LIBEXEC_GHC_STAGE_TO_GHC = YES +ifeq "$(Stage1Only) $(Windows_Host)" "YES YES" +# resulting ghc-stage1 is built to run on windows +RENAME_LIBEXEC_GHC_STAGE_TO_GHC = NO +endif +ifeq "$(Stage1Only) $(Windows_Target)" "NO YES" +# resulting ghc-stage1 is built to run on windows +RENAME_LIBEXEC_GHC_STAGE_TO_GHC = NO +endif + install_libexecs: $(INSTALL_LIBEXECS) ifneq "$(INSTALL_LIBEXECS)" "" $(INSTALL_DIR) "$(DESTDIR)$(ghclibexecdir)/bin" for i in $(INSTALL_LIBEXECS); do \ $(INSTALL_PROGRAM) $(INSTALL_BIN_OPTS) $$i "$(DESTDIR)$(ghclibexecdir)/bin"; \ done -# We rename ghc-stage2, so that the right program name is used in error -# messages etc. -ifeq "$(Windows_Target)" "NO" +ifeq "$(RENAME_LIBEXEC_GHC_STAGE_TO_GHC)" "YES" "$(MV)" "$(DESTDIR)$(ghclibexecdir)/bin/ghc-stage$(INSTALL_GHC_STAGE)" "$(DESTDIR)$(ghclibexecdir)/bin/ghc" endif endif From git at git.haskell.org Tue May 23 14:57:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 May 2017 14:57:45 +0000 (UTC) Subject: [commit: ghc] master: rts: Make compact debugging output depend upon compact debug flag (a29132e) Message-ID: <20170523145745.C72B43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a29132e9248e39a45673b5c146341d9f4947dacd/ghc >--------------------------------------------------------------- commit a29132e9248e39a45673b5c146341d9f4947dacd Author: Ben Gamari Date: Tue May 23 10:33:58 2017 -0400 rts: Make compact debugging output depend upon compact debug flag >--------------------------------------------------------------- a29132e9248e39a45673b5c146341d9f4947dacd rts/sm/CNF.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/sm/CNF.c b/rts/sm/CNF.c index cec0e31..c12f53a 100644 --- a/rts/sm/CNF.c +++ b/rts/sm/CNF.c @@ -1131,7 +1131,7 @@ maybe_fixup_internal_pointers (StgCompactNFDataBlock *block, if (!any_needs_fixup(block)) return root; - IF_DEBUG(gc, debugBelch("Compact imported at the wrong address, " + IF_DEBUG(compact, debugBelch("Compact imported at the wrong address, " "will fix up internal pointers\n")); // I am PROOT! From git at git.haskell.org Tue May 23 14:57:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 May 2017 14:57:48 +0000 (UTC) Subject: [commit: ghc] master: base: Fix a few TODOs in Typeable.Internal (6166b59) Message-ID: <20170523145748.9438A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6166b59fadb8714cd497902c8469fd2b3b6caf46/ghc >--------------------------------------------------------------- commit 6166b59fadb8714cd497902c8469fd2b3b6caf46 Author: Ben Gamari Date: Tue May 23 09:42:12 2017 -0400 base: Fix a few TODOs in Typeable.Internal Test Plan: Validate Reviewers: austin, hvr, dfeuer Reviewed By: dfeuer Subscribers: rwbarton, thomie GHC Trac Issues: #13746 Differential Revision: https://phabricator.haskell.org/D3605 >--------------------------------------------------------------- 6166b59fadb8714cd497902c8469fd2b3b6caf46 libraries/base/Data/Typeable/Internal.hs | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 48da8dd..cf645ad 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -187,9 +187,6 @@ data TypeRep (a :: k) where -> TypeRep b -> TypeRep (a -> b) -on :: (a -> a -> r) -> (b -> a) -> (b -> b -> r) -on f g = \ x y -> g x `f` g y - -- Compare keys for equality -- | @since 2.01 @@ -207,7 +204,8 @@ instance TestEquality TypeRep where -- | @since 4.4.0.0 instance Ord (TypeRep a) where - compare = compare `on` typeRepFingerprint + compare _ _ = EQ + {-# INLINABLE compare #-} -- | A non-indexed type representation. data SomeTypeRep where @@ -305,11 +303,11 @@ someTypeRepTyCon (SomeTypeRep t) = typeRepTyCon t typeRepTyCon :: TypeRep a -> TyCon typeRepTyCon (TrTyCon _ tc _) = tc typeRepTyCon (TrApp _ a _) = typeRepTyCon a -typeRepTyCon (TrFun _ _ _) = error "typeRepTyCon: FunTy" -- TODO +typeRepTyCon (TrFun _ _ _) = typeRepTyCon $ typeRep @(->) -- | Type equality -- --- @since TODO +-- @since 4.10 eqTypeRep :: forall k1 k2 (a :: k1) (b :: k2). TypeRep a -> TypeRep b -> Maybe (a :~~: b) eqTypeRep a b From git at git.haskell.org Tue May 23 15:01:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 May 2017 15:01:51 +0000 (UTC) Subject: [commit: ghc] master: Typos in comments and manual [ci skip] (0b4b4a3) Message-ID: <20170523150151.780A03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0b4b4a346e6922dafb073693593d55c7e87be9ca/ghc >--------------------------------------------------------------- commit 0b4b4a346e6922dafb073693593d55c7e87be9ca Author: Gabor Greif Date: Tue May 23 12:08:25 2017 +0200 Typos in comments and manual [ci skip] >--------------------------------------------------------------- 0b4b4a346e6922dafb073693593d55c7e87be9ca compiler/cmm/CmmUtils.hs | 2 +- compiler/coreSyn/TrieMap.hs | 2 +- compiler/rename/RnExpr.hs | 2 +- docs/users_guide/using-optimisation.rst | 4 ++-- mk/config.mk.in | 6 +++--- 5 files changed, 8 insertions(+), 8 deletions(-) diff --git a/compiler/cmm/CmmUtils.hs b/compiler/cmm/CmmUtils.hs index 1dab6ee..722718a 100644 --- a/compiler/cmm/CmmUtils.hs +++ b/compiler/cmm/CmmUtils.hs @@ -510,7 +510,7 @@ toBlockListEntryFirst g -- have both true and false successors. Block ordering can make a big difference -- in performance in the LLVM backend. Note that we rely crucially on the order -- of successors returned for CmmCondBranch by the NonLocal instance for CmmNode --- defind in cmm/CmmNode.hs. -GBM +-- defined in cmm/CmmNode.hs. -GBM toBlockListEntryFirstFalseFallthrough :: CmmGraph -> [CmmBlock] toBlockListEntryFirstFalseFallthrough g | mapNull m = [] diff --git a/compiler/coreSyn/TrieMap.hs b/compiler/coreSyn/TrieMap.hs index 308a953..9058d03 100644 --- a/compiler/coreSyn/TrieMap.hs +++ b/compiler/coreSyn/TrieMap.hs @@ -446,7 +446,7 @@ Note [Binders] rather than cm_lam :: TypeMapG (CoreMapG a) - * We don't need to look at the type of some binders, notalby + * We don't need to look at the type of some binders, notably - the case binder in (Case _ b _ _) - the binders in an alternative because they are totally fixed by the context diff --git a/compiler/rename/RnExpr.hs b/compiler/rename/RnExpr.hs index cf0326e..027f6dc 100644 --- a/compiler/rename/RnExpr.hs +++ b/compiler/rename/RnExpr.hs @@ -833,7 +833,7 @@ rnStmt ctxt rnBody (L loc (BindStmt pat body _ _ _)) thing_inside ; xMonadFailEnabled <- fmap (xopt LangExt.MonadFailDesugaring) getDynFlags ; let getFailFunction - -- If the pattern is irrefutible (e.g.: wildcard, tuple, + -- If the pattern is irrefutable (e.g.: wildcard, tuple, -- ~pat, etc.) we should not need to fail. | isIrrefutableHsPat pat = return (noSyntaxExpr, emptyFVs) diff --git a/docs/users_guide/using-optimisation.rst b/docs/users_guide/using-optimisation.rst index cfecc34..1e74b71 100644 --- a/docs/users_guide/using-optimisation.rst +++ b/docs/users_guide/using-optimisation.rst @@ -648,7 +648,7 @@ by saying ``-fno-wombat``. :default: on When solving constraints, try to eagerly solve - super classes using availible dictionaries. + super classes using available dictionaries. For example:: @@ -663,7 +663,7 @@ by saying ``-fno-wombat``. constraint from the context because we have `C Int b` and that provides us a solution for `Num Int`. However, we can often produce much better code - by directly solving for an availible `Num Int` dictionary we might have at + by directly solving for an available `Num Int` dictionary we might have at hand. This removes potentially many layers of indirection and crucially allows other optimisations to fire as the dictionary will be statically known and selector functions can be inlined. diff --git a/mk/config.mk.in b/mk/config.mk.in index b2a9569..189439e 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -893,7 +893,7 @@ GMP_LIB_DIRS = @GMP_LIB_DIRS@ CURSES_INCLUDE_DIRS = @CURSES_INCLUDE_DIRS@ CURSES_LIB_DIRS = @CURSES_LIB_DIRS@ -# See Note [Disable -O2 in unregisteride mode] +# See Note [Disable -O2 in unregisterised mode] # Be careful: 'GhcUnregisterised' should be defined earlier in this file. ifeq "$(GhcUnregisterised)" "YES" GhcStage1HcOpts= @@ -903,8 +903,8 @@ GhcStage3HcOpts= GhcLibHcOpts= endif -# Note [Disable -O2 in unregisteride mode] -# Disable -O2 optimization in uregisterised more. Otherwise amount +# Note [Disable -O2 in unregisterised mode] +# Disable -O2 optimization in unregisterised mode. Otherwise amount # of generated C code # makes things very slow to compile (~5 minutes # on core-i7 for 'compiler/hsSyn/HsExpr.hs') and sometimes not compile # at all: powerpc64 overflows TOC section on 'compiler/hsSyn/HsExpr.hs' From git at git.haskell.org Tue May 23 23:47:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 May 2017 23:47:30 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix the pure unifier (aa39137) Message-ID: <20170523234730.829923A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/aa39137316fcbb555bcb676cb2f89002d97d3e3c/ghc >--------------------------------------------------------------- commit aa39137316fcbb555bcb676cb2f89002d97d3e3c Author: Simon Peyton Jones Date: Tue May 16 15:43:55 2017 +0100 Fix the pure unifier This patch fixes Trac #13705, by fixing a long-standing outright bug in the pure unifier. I'm surprised this hasn't caused more trouble before now! (cherry picked from commit cec7d580c2c033c3aaeba093752328d8f3635cd0) >--------------------------------------------------------------- aa39137316fcbb555bcb676cb2f89002d97d3e3c compiler/types/Unify.hs | 380 ++++++++++----------- .../tests/indexed-types/should_compile/T13705.hs | 15 + testsuite/tests/indexed-types/should_compile/all.T | 1 + 3 files changed, 200 insertions(+), 196 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 aa39137316fcbb555bcb676cb2f89002d97d3e3c From git at git.haskell.org Tue May 23 23:47:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 May 2017 23:47:33 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Account for IfUnpackCo in freeNamesIfDecl (1e93425) Message-ID: <20170523234733.37EAD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/1e93425ee78481f10f79cb1d39b6cd4f11f38e5d/ghc >--------------------------------------------------------------- commit 1e93425ee78481f10f79cb1d39b6cd4f11f38e5d Author: Simon Peyton Jones Date: Fri May 19 12:00:26 2017 +0100 Account for IfUnpackCo in freeNamesIfDecl We were simply failing to recognise all the free variables of an IfaceDecl, notably the ones in the coercion of an IfUnpackCo. Result: the dependency analysis got messed up, so that fingerprint calculation went wrong. Trac #13695 showed it up. A test case is tricky but the fix is a solid one. (cherry picked from commit 8fe37a0222517c3af5ffbb793fa738ad7f3eac3d) >--------------------------------------------------------------- 1e93425ee78481f10f79cb1d39b6cd4f11f38e5d compiler/iface/IfaceSyn.hs | 21 +++++++++++++++------ 1 file changed, 15 insertions(+), 6 deletions(-) diff --git a/compiler/iface/IfaceSyn.hs b/compiler/iface/IfaceSyn.hs index 5db8c99..6f8fcf4 100644 --- a/compiler/iface/IfaceSyn.hs +++ b/compiler/iface/IfaceSyn.hs @@ -1345,12 +1345,21 @@ freeNamesIfConDecls (IfNewTyCon c) = freeNamesIfConDecl c freeNamesIfConDecls _ = emptyNameSet freeNamesIfConDecl :: IfaceConDecl -> NameSet -freeNamesIfConDecl c - = freeNamesIfTyVarBndrs (ifConExTvs c) &&& - freeNamesIfContext (ifConCtxt c) &&& - fnList freeNamesIfType (ifConArgTys c) &&& - mkNameSet (map flSelector (ifConFields c)) &&& - fnList freeNamesIfType (map snd (ifConEqSpec c)) -- equality constraints +freeNamesIfConDecl (IfCon { ifConExTvs = ex_tvs, ifConCtxt = ctxt + , ifConArgTys = arg_tys + , ifConFields = flds + , ifConEqSpec = eq_spec + , ifConStricts = bangs }) + = freeNamesIfTyVarBndrs ex_tvs &&& + freeNamesIfContext ctxt &&& + fnList freeNamesIfType arg_tys &&& + mkNameSet (map flSelector flds) &&& + fnList freeNamesIfType (map snd eq_spec) &&& -- equality constraints + fnList freeNamesIfBang bangs + +freeNamesIfBang :: IfaceBang -> NameSet +freeNamesIfBang (IfUnpackCo co) = freeNamesIfCoercion co +freeNamesIfBang _ = emptyNameSet freeNamesIfKind :: IfaceType -> NameSet freeNamesIfKind = freeNamesIfType From git at git.haskell.org Tue May 23 23:47:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 May 2017 23:47:36 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Handle type-lets better (c7d8099) Message-ID: <20170523234736.9F2513A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/c7d809928d87a7a54bcea6badea3e7ee5f7181db/ghc >--------------------------------------------------------------- commit c7d809928d87a7a54bcea6badea3e7ee5f7181db Author: Simon Peyton Jones Date: Wed May 17 09:44:46 2017 +0100 Handle type-lets better Core allows non-recursive type-lets, thus let a = TYPE ty in ... They are substituted away very quickly, but it's convenient for some passes to produce them (rather than to have to substitute immediately). Trac #13708 tried the effect of not running the simplifer at all (a rather bizarre thing to do, but still). That showed that some passes crashed because they always treated a let-bounder binder as an Id. This patch adds some easy fixes. (cherry picked from commit d6461f9684f6f758320a5e5afbf0634fcc2996a5) >--------------------------------------------------------------- c7d809928d87a7a54bcea6badea3e7ee5f7181db compiler/basicTypes/Id.hs | 6 +++-- compiler/basicTypes/Var.hs | 4 ++-- compiler/coreSyn/CoreFVs.hs | 27 ++++++++-------------- compiler/simplCore/CSE.hs | 14 +++++++---- compiler/simplCore/FloatIn.hs | 4 ++-- testsuite/tests/simplCore/should_compile/T13708.hs | 11 +++++++++ testsuite/tests/simplCore/should_compile/all.T | 1 + 7 files changed, 39 insertions(+), 28 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 c7d809928d87a7a54bcea6badea3e7ee5f7181db From git at git.haskell.org Tue May 23 23:47:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 May 2017 23:47:39 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: rts: Make compact debugging output depend upon compact debug flag (367ad4c) Message-ID: <20170523234739.58DCB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/367ad4c0500759e5e8d4459caed872da0148b381/ghc >--------------------------------------------------------------- commit 367ad4c0500759e5e8d4459caed872da0148b381 Author: Ben Gamari Date: Tue May 23 10:33:58 2017 -0400 rts: Make compact debugging output depend upon compact debug flag (cherry picked from commit a29132e9248e39a45673b5c146341d9f4947dacd) >--------------------------------------------------------------- 367ad4c0500759e5e8d4459caed872da0148b381 rts/sm/CNF.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/sm/CNF.c b/rts/sm/CNF.c index 3892132..edb547f 100644 --- a/rts/sm/CNF.c +++ b/rts/sm/CNF.c @@ -1125,7 +1125,7 @@ maybe_fixup_internal_pointers (StgCompactNFDataBlock *block, if (!any_needs_fixup(block)) return root; - IF_DEBUG(gc, debugBelch("Compact imported at the wrong address, " + IF_DEBUG(compact, debugBelch("Compact imported at the wrong address, " "will fix up internal pointers\n")); // I am PROOT! From git at git.haskell.org Tue May 23 23:47:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 May 2017 23:47:42 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: base: Fix a few TODOs in Typeable.Internal (979cc34) Message-ID: <20170523234742.0DDAC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/979cc34b03909939c007e7b719687362dbfdf153/ghc >--------------------------------------------------------------- commit 979cc34b03909939c007e7b719687362dbfdf153 Author: Ben Gamari Date: Tue May 23 09:42:12 2017 -0400 base: Fix a few TODOs in Typeable.Internal Test Plan: Validate Reviewers: austin, hvr, dfeuer Reviewed By: dfeuer Subscribers: rwbarton, thomie GHC Trac Issues: #13746 Differential Revision: https://phabricator.haskell.org/D3605 (cherry picked from commit 6166b59fadb8714cd497902c8469fd2b3b6caf46) >--------------------------------------------------------------- 979cc34b03909939c007e7b719687362dbfdf153 libraries/base/Data/Typeable/Internal.hs | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 48da8dd..cf645ad 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -187,9 +187,6 @@ data TypeRep (a :: k) where -> TypeRep b -> TypeRep (a -> b) -on :: (a -> a -> r) -> (b -> a) -> (b -> b -> r) -on f g = \ x y -> g x `f` g y - -- Compare keys for equality -- | @since 2.01 @@ -207,7 +204,8 @@ instance TestEquality TypeRep where -- | @since 4.4.0.0 instance Ord (TypeRep a) where - compare = compare `on` typeRepFingerprint + compare _ _ = EQ + {-# INLINABLE compare #-} -- | A non-indexed type representation. data SomeTypeRep where @@ -305,11 +303,11 @@ someTypeRepTyCon (SomeTypeRep t) = typeRepTyCon t typeRepTyCon :: TypeRep a -> TyCon typeRepTyCon (TrTyCon _ tc _) = tc typeRepTyCon (TrApp _ a _) = typeRepTyCon a -typeRepTyCon (TrFun _ _ _) = error "typeRepTyCon: FunTy" -- TODO +typeRepTyCon (TrFun _ _ _) = typeRepTyCon $ typeRep @(->) -- | Type equality -- --- @since TODO +-- @since 4.10 eqTypeRep :: forall k1 k2 (a :: k1) (b :: k2). TypeRep a -> TypeRep b -> Maybe (a :~~: b) eqTypeRep a b From git at git.haskell.org Tue May 23 23:47:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 May 2017 23:47:44 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: rts: Revert unintentional changes in Libdw.c (9410a4c) Message-ID: <20170523234744.B72643A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/9410a4c8a710fc59ad8b03b94302d7cb6b9c92f3/ghc >--------------------------------------------------------------- commit 9410a4c8a710fc59ad8b03b94302d7cb6b9c92f3 Author: Ben Gamari Date: Tue May 23 19:46:24 2017 -0400 rts: Revert unintentional changes in Libdw.c These snuck in to 66d5e8015bed91fd0e2091641fe855c433c24b6c. >--------------------------------------------------------------- 9410a4c8a710fc59ad8b03b94302d7cb6b9c92f3 rts/Libdw.c | 83 ++++++++++--------------------------------------------------- 1 file changed, 13 insertions(+), 70 deletions(-) diff --git a/rts/Libdw.c b/rts/Libdw.c index d949217..a16ea59 100644 --- a/rts/Libdw.c +++ b/rts/Libdw.c @@ -18,8 +18,6 @@ const int max_backtrace_depth = 5000; -static bool set_initial_registers(Dwfl_Thread *thread, void *arg); - static BacktraceChunk *backtraceAllocChunk(BacktraceChunk *next) { BacktraceChunk *chunk = stgMallocBytes(sizeof(BacktraceChunk), "backtraceAllocChunk"); @@ -61,13 +59,14 @@ void backtraceFree(Backtrace *bt) { struct LibdwSession_ { Dwfl *dwfl; - Dwfl_Thread_Callbacks thread_cbs; // The current backtrace we are collecting (if any) Backtrace *cur_bt; int max_depth; }; +static const Dwfl_Thread_Callbacks thread_cbs; + void libdwFree(LibdwSession *session) { if (session == NULL) return; @@ -112,7 +111,6 @@ LibdwSession *libdwInit() { goto fail; } - pid_t pid = getpid(); if (! dwfl_attach_state(session->dwfl, NULL, pid, &thread_cbs, NULL)) { sysErrorBelch("dwfl_attach_state failed: %s", @@ -245,62 +243,11 @@ static int getBacktraceFrameCb(Dwfl_Frame *frame, void *arg) { } } -static pid_t next_tso(Dwfl *dwfl, void *arg, void **thread_argp) { - /* there is only the current thread */ - if (*thread_argp != NULL) - return 0; - - *thread_argp = tso; - return dwfl_pid(dwfl); -} - -int forEachHsThread(LibdwSession *session, int (*do_it)(StgTSO *)) { - tso_list *list = NULL; - for (int g = 0; g < RtsFlags.GcFlags.generations; g++) { - for (StgTSO *t = generations[g].threads; t != END_TSO_QUEUE; t = t->global_link) { - int ret = do_it(t); - if (ret) return ret; - } - } - return 0; -} - -/* Collect a backtrace for the thread associated with the given TSO */ -Backtrace *libdwGetThreadBacktrace(LibdwSession *session, StgTSO *tso) { - if (session->cur_bt != NULL) { - sysErrorBelch("Already collecting backtrace. Uh oh."); - return NULL; - } - - session->thread_cbs = { - .next_thread = dummy_next_thread, - .memory_read = memory_read, - .set_initial_registers = set_tso_initial_registers, - }; - - Backtrace *bt = backtraceAlloc(); - session->cur_bt = bt; - session->max_depth = max_backtrace_depth; - int ret = dwfl_getthread_frames(session->dwfl, tso, getBacktraceFrameCb, session); - if (ret == -1) - sysErrorBelch("Failed to get stack frames of current process: %s", - dwfl_errmsg(dwfl_errno())); - - session->cur_bt = NULL; - return bt; -} - -/* Collect a backtrace of the current execution stack */ Backtrace *libdwGetBacktrace(LibdwSession *session) { if (session->cur_bt != NULL) { sysErrorBelch("Already collecting backtrace. Uh oh."); return NULL; } - session->thread_cbs = { - .next_thread = dummy_next_thread, - .memory_read = memory_read, - .set_initial_registers = set_current_initial_registers, - }; Backtrace *bt = backtraceAlloc(); session->cur_bt = bt; @@ -317,9 +264,7 @@ Backtrace *libdwGetBacktrace(LibdwSession *session) { return bt; } -/* the libdwfl next_thread callback for when we are collecting a backtrace for - the current thread */ -static pid_t dummy_next_thread(Dwfl *dwfl, void *arg, void **thread_argp) { +static pid_t next_thread(Dwfl *dwfl, void *arg, void **thread_argp) { /* there is only the current thread */ if (*thread_argp != NULL) return 0; @@ -328,24 +273,17 @@ static pid_t dummy_next_thread(Dwfl *dwfl, void *arg, void **thread_argp) { return dwfl_pid(dwfl); } -/* libdwfl memory_read callback to read from the current process */ static bool memory_read(Dwfl *dwfl STG_UNUSED, Dwarf_Addr addr, Dwarf_Word *result, void *arg STG_UNUSED) { *result = *(Dwarf_Word *) (uintptr_t) addr; return true; } -#ifdef x86_64_HOST_ARCH -static bool set_tso_initial_registers(Dwfl_Thread *thread, void *arg) { - StgTSO *tso = arg; - Dwarf_Word regs[17]; - regs[6] = tso->stackobj->sp; // rbp - regs[16] = tso->stackobj->sp[0]; // rip - return dwfl_thread_state_registers(thread, 0, 17, regs); -} +static bool set_initial_registers(Dwfl_Thread *thread, void *arg); -static bool set_current_initial_registers(Dwfl_Thread *thread, - void *arg STG_UNUSED) { +#ifdef x86_64_HOST_ARCH +static bool set_initial_registers(Dwfl_Thread *thread, + void *arg STG_UNUSED) { Dwarf_Word regs[17]; __asm__ ("movq %%rax, 0x00(%0)\n\t" "movq %%rdx, 0x08(%0)\n\t" @@ -371,7 +309,6 @@ static bool set_current_initial_registers(Dwfl_Thread *thread, ); return dwfl_thread_state_registers(thread, 0, 17, regs); } - #elif defined(i386_HOST_ARCH) static bool set_initial_registers(Dwfl_Thread *thread, void *arg STG_UNUSED) { @@ -397,6 +334,12 @@ static bool set_initial_registers(Dwfl_Thread *thread, # error "Please implement set_initial_registers() for your arch" #endif +static const Dwfl_Thread_Callbacks thread_cbs = { + .next_thread = next_thread, + .memory_read = memory_read, + .set_initial_registers = set_initial_registers, +}; + #else /* !USE_LIBDW */ void backtraceFree(Backtrace *bt STG_UNUSED) { } From git at git.haskell.org Wed May 24 09:30:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 24 May 2017 09:30:39 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T13719' created Message-ID: <20170524093039.D01BE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T13719 Referencing: 17d59b9e979db9fe1b7ed6e03620fb4ea6045873 From git at git.haskell.org Wed May 24 09:30:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 24 May 2017 09:30:42 +0000 (UTC) Subject: [commit: ghc] wip/T13719: Faster checkFamInstConsistency (17d59b9) Message-ID: <20170524093042.924763A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T13719 Link : http://ghc.haskell.org/trac/ghc/changeset/17d59b9e979db9fe1b7ed6e03620fb4ea6045873/ghc >--------------------------------------------------------------- commit 17d59b9e979db9fe1b7ed6e03620fb4ea6045873 Author: Bartosz Nitka Date: Fri May 19 08:08:01 2017 -0700 Faster checkFamInstConsistency Summary: This implements the idea from https://ghc.haskell.org/trac/ghc/ticket/13092#comment:14. It's explained in Note [Checking family instance optimization] in more detail. This improves the test case T13719 tenfold and cuts down the compile time on `:load` in `ghci` on our internal code base by half. Test Plan: ./validate Reviewers: simonpj, simonmar, rwbarton, austin, bgamari Subscribers: thomie GHC Trac Issues: #13719 Differential Revision: https://phabricator.haskell.org/D3603 >--------------------------------------------------------------- 17d59b9e979db9fe1b7ed6e03620fb4ea6045873 compiler/typecheck/FamInst.hs | 218 ++++++++++++++++++++++-------------- compiler/typecheck/TcRnDriver.hs | 2 +- testsuite/tests/perf/compiler/all.T | 3 +- 3 files changed, 135 insertions(+), 88 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 17d59b9e979db9fe1b7ed6e03620fb4ea6045873 From git at git.haskell.org Thu May 25 10:59:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 25 May 2017 10:59:32 +0000 (UTC) Subject: [commit: ghc] master: Comments only (1013194) Message-ID: <20170525105932.2427F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/10131947b212770c837035f042a11c024cf0ec67/ghc >--------------------------------------------------------------- commit 10131947b212770c837035f042a11c024cf0ec67 Author: Simon Peyton Jones Date: Thu May 25 09:59:09 2017 +0100 Comments only >--------------------------------------------------------------- 10131947b212770c837035f042a11c024cf0ec67 compiler/typecheck/TcCanonical.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index f533750..5dddd5d 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -1297,10 +1297,9 @@ representational equality, this is a little subtler. Once again, (a ~R [a]) is a bad thing, but (a ~R N a) for a newtype N might be just fine. This means also that (a ~ b a) might be fine, because `b` might become a newtype. -So, we must check: does tv1 appear in xi2 under any type constructor that -is generative w.r.t. representational equality? That's what isTyVarUnderDatatype -does. (The other name I considered, isTyVarUnderTyConGenerativeWrtReprEq was -a bit verbose. And the shorter name gets the point across.) +So, we must check: does tv1 appear in xi2 under any type constructor +that is generative w.r.t. representational equality? That's what +isInsolubleOccursCheck does. See also #10715, which induced this addition. From git at git.haskell.org Thu May 25 10:59:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 25 May 2017 10:59:35 +0000 (UTC) Subject: [commit: ghc] master: Pattern synonyms and higher rank types (c997738) Message-ID: <20170525105935.96EBD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c9977385dca9536f18374242f713b1048a38dec5/ghc >--------------------------------------------------------------- commit c9977385dca9536f18374242f713b1048a38dec5 Author: Simon Peyton Jones Date: Thu May 25 09:59:29 2017 +0100 Pattern synonyms and higher rank types This patch fixes two separate bugs which contributed to making Trac #13752 go wrong 1. We need to use tcSubType, not tcUnify, in tcCheckPatSynDecl.tc_arg. Reason: Note [Pattern synonyms and higher rank types] 2. TcUnify.tc_sub_type had a special case designed to improve error messages; see Note [Don't skolemise unnecessarily]. But the special case was too liberal, and ended up using unification (which led to rejecting the program) when it should instead taken the normal path (which accepts the program). I fixed this by making the test more conservative. >--------------------------------------------------------------- c9977385dca9536f18374242f713b1048a38dec5 compiler/typecheck/TcPatSyn.hs | 24 ++++++++++--- compiler/typecheck/TcUnify.hs | 46 +++++++++++++++++++----- testsuite/tests/patsyn/should_compile/T13752.hs | 9 +++++ testsuite/tests/patsyn/should_compile/T13752a.hs | 8 +++++ testsuite/tests/patsyn/should_compile/all.T | 2 ++ 5 files changed, 75 insertions(+), 14 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index 4b4b042..dc2c4de 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -192,12 +192,26 @@ tcCheckPatSynDecl psb at PSB{ psb_id = lname@(L _ name), psb_args = details = do { -- Look up the variable actually bound by lpat -- and check that it has the expected type arg_id <- tcLookupId arg_name - ; coi <- unifyType (Just arg_id) - (idType arg_id) - (substTyUnchecked subst arg_ty) - ; return (mkLHsWrapCo coi $ nlHsVar arg_id) } + ; wrap <- tcSubType_NC GenSigCtxt + (idType arg_id) + (substTyUnchecked subst arg_ty) + -- Why do we need tcSubType here? + -- See Note [Pattern synonyms and higher rank types] + ; return (mkLHsWrap wrap $ nlHsVar arg_id) } + +{- [Pattern synonyms and higher rank types] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider + data T = MkT (forall a. a->a) + + pattern P :: (Int -> Int) -> T + pattern P x <- MkT x + +This should work. But in the matcher we must match against MkT, and then +instantiate its argument 'x', to get a functino of type (Int -> Int). +Equality is not enough! Trac #13752 was an example. -{- Note [Checking against a pattern signature] +Note [Checking against a pattern signature] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When checking the actual supplied pattern against the pattern synonym signature, we need to be quite careful. diff --git a/compiler/typecheck/TcUnify.hs b/compiler/typecheck/TcUnify.hs index 6bb81d9..e103d20 100644 --- a/compiler/typecheck/TcUnify.hs +++ b/compiler/typecheck/TcUnify.hs @@ -638,8 +638,8 @@ tc_sub_tc_type :: CtOrigin -- used when calling uType -- If wrap = tc_sub_type t1 t2 -- => wrap :: t1 ~> t2 tc_sub_tc_type eq_orig inst_orig ctxt ty_actual ty_expected - | is_poly ty_expected -- See Note [Don't skolemise unnecessarily] - , not (is_poly ty_actual) + | definitely_poly ty_expected -- See Note [Don't skolemise unnecessarily] + , not (possibly_poly ty_actual) = do { traceTc "tc_sub_tc_type (drop to equality)" $ vcat [ text "ty_actual =" <+> ppr ty_actual , text "ty_expected =" <+> ppr ty_expected ] @@ -656,13 +656,21 @@ tc_sub_tc_type eq_orig inst_orig ctxt ty_actual ty_expected ty_actual sk_rho ; return (sk_wrap <.> inner_wrap) } where - is_poly ty + possibly_poly ty | isForAllTy ty = True - | Just (_, res) <- splitFunTy_maybe ty = is_poly res + | Just (_, res) <- splitFunTy_maybe ty = possibly_poly res | otherwise = False -- NB *not* tcSplitFunTy, because here we want -- to decompose type-class arguments too + definitely_poly ty + | (tvs, theta, tau) <- tcSplitSigmaTy ty + , (tv:_) <- tvs + , null theta + , isInsolubleOccursCheck NomEq tv tau + = True + | otherwise + = False {- Note [Don't skolemise unnecessarily] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -674,11 +682,31 @@ error. It's better to say that (Char->Char) ~ (forall a. a->a) fails. -In general, - * if the RHS type an outermost forall (i.e. skolemisation - is the next thing we'd do) - * and the LHS has no top-level polymorphism (but looking deeply) -then we can revert to simple equality. +So roughly: + * if the ty_expected has an outermost forall + (i.e. skolemisation is the next thing we'd do) + * and the ty_actual has no top-level polymorphism (but looking deeply) +then we can revert to simple equality. But we need to be careful. +These examples are allfine: + + * (Char -> forall a. a->a) <= (forall a. Char -> a -> a) + Polymorphism is buried in ty_actual + + * (Char->Char) <= (forall a. Char -> Char) + ty_expected isn't really polymorphic + + * (Char->Char) <= (forall a. (a~Char) => a -> a) + ty_expected isn't really polymorphic + + * (Char->Char) <= (forall a. F [a] Char -> Char) + where type instance F [x] t = t + ty_expected isn't really polymorphic + +If we prematurely go to equality we'll reject a program we should +accept (e.g. Grac #13752). So the test (which is only to improve +error messagse) is very conservative: + * ty_actual is /definitely/ monomorphic + * ty_expected is /definitely/ polymorphic -} --------------- diff --git a/testsuite/tests/patsyn/should_compile/T13752.hs b/testsuite/tests/patsyn/should_compile/T13752.hs new file mode 100644 index 0000000..f9ff606 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T13752.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE TypeFamilies, ConstraintKinds, PatternSynonyms, RankNTypes #-} + +module T13752 where + +newtype Arrange = Arrange {getArrange :: [Int] -> [Int]} + +pattern Heh :: (c ~ ((~) Int)) => (forall a. c a => [a] -> [a]) -> Arrange +-- pattern Heh :: (forall a. (Int ~ a) => [a] -> [a]) -> Arrange +pattern Heh f <- Arrange f diff --git a/testsuite/tests/patsyn/should_compile/T13752a.hs b/testsuite/tests/patsyn/should_compile/T13752a.hs new file mode 100644 index 0000000..2c417f9 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T13752a.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE PatternSynonyms, RankNTypes #-} + +module T13752a where + +data T = MkT (forall a. a->a) + +pattern P :: (Int -> Int) -> T +pattern P x <- MkT x diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index fa8a3d8..30319c7 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -68,3 +68,5 @@ test('T13441', normal, compile, ['']) test('T13441a', normal, compile, ['']) test('T13441b', normal, compile_fail, ['']) test('T13454', normal, compile, ['']) +test('T13752', normal, compile, ['']) +test('T13752a', normal, compile, ['']) From git at git.haskell.org Thu May 25 21:55:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 25 May 2017 21:55:24 +0000 (UTC) Subject: [commit: ghc] master: rules: add per-library EXTRA_HC_OPTS (f011f58) Message-ID: <20170525215524.77DF53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f011f587ca0289e96dd26acfc5f40a66aa7d6e5f/ghc >--------------------------------------------------------------- commit f011f587ca0289e96dd26acfc5f40a66aa7d6e5f Author: Sergei Trofimovich Date: Thu May 25 22:44:37 2017 +0100 rules: add per-library EXTRA_HC_OPTS Sometimes it's handy to change a compiler flag for a library in stage{0,1,2}. Usage example: libraries/binary_EXTRA_HC_OPTS += -O1 libraries/containers_EXTRA_HC_OPTS += -O1 libraries/bytestring_EXTRA_HC_OPTS += -O1 Here override default -O2 defined in .cabal files for these libraries to speed build up. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- f011f587ca0289e96dd26acfc5f40a66aa7d6e5f rules/distdir-way-opts.mk | 1 + 1 file changed, 1 insertion(+) diff --git a/rules/distdir-way-opts.mk b/rules/distdir-way-opts.mk index c4d7168..eb4a5c4 100644 --- a/rules/distdir-way-opts.mk +++ b/rules/distdir-way-opts.mk @@ -145,6 +145,7 @@ $1_$2_$3_MOST_HC_OPTS = \ $$($1_$2_HC_OPTS) \ $$(CONF_HC_OPTS_STAGE$4) \ $$($1_$2_MORE_HC_OPTS) \ + $$($1_EXTRA_HC_OPTS) \ $$($1_$2_EXTRA_HC_OPTS) \ $$($1_$2_$3_HC_OPTS) \ $$($$(basename $$(subst ./,,$$<))_HC_OPTS) \ From git at git.haskell.org Fri May 26 08:55:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 May 2017 08:55:14 +0000 (UTC) Subject: [commit: ghc] master: A bit more tc-tracing (17055da) Message-ID: <20170526085514.A206F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/17055da185b8e3ba03f92401f1c0f7a225f55e00/ghc >--------------------------------------------------------------- commit 17055da185b8e3ba03f92401f1c0f7a225f55e00 Author: Simon Peyton Jones Date: Fri May 26 09:24:14 2017 +0100 A bit more tc-tracing >--------------------------------------------------------------- 17055da185b8e3ba03f92401f1c0f7a225f55e00 compiler/typecheck/TcTyClsDecls.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index ddb183d..cb46c69 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -555,7 +555,11 @@ getFamDeclInitialKind mb_cusk decl@(FamilyDecl { fdLName = L _ name kcLTyClDecl :: LTyClDecl Name -> TcM () -- See Note [Kind checking for type and class decls] kcLTyClDecl (L loc decl) - = setSrcSpan loc $ tcAddDeclCtxt decl $ kcTyClDecl decl + = setSrcSpan loc $ + tcAddDeclCtxt decl $ + do { traceTc "kcTyClDecl {" (ppr (tyClDeclLName decl)) + ; kcTyClDecl decl + ; traceTc "kcTyClDecl done }" (ppr (tyClDeclLName decl)) } kcTyClDecl :: TyClDecl Name -> TcM () -- This function is used solely for its side effect on kind variables From git at git.haskell.org Fri May 26 08:55:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 May 2017 08:55:18 +0000 (UTC) Subject: [commit: ghc] master: Re-engineer Given flatten-skolems (8dc6d64) Message-ID: <20170526085518.00ADB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8dc6d645fc3384b3b8ded0578939f5c855dd2ed5/ghc >--------------------------------------------------------------- commit 8dc6d645fc3384b3b8ded0578939f5c855dd2ed5 Author: Simon Peyton Jones Date: Fri May 26 09:31:38 2017 +0100 Re-engineer Given flatten-skolems The big change here is to fix an outright bug in flattening of Givens, albeit one that is very hard to exhibit. Suppose we have the constraint forall a. (a ~ F b) => ..., (forall c. ....(F b)...) ... Then - we'll flatten the (F) b to a fsk, say (F b ~ fsk1) - we'll rewrite the (F b) inside the inner implication to 'fsk1' - when we leave the outer constraint we are suppose to unflatten; but that fsk1 will still be there - if we re-simplify the entire outer implication, we'll re-flatten the Given (F b) to, say, (F b ~ fsk2) Now we have two fsks standing for the same thing, and that is very wrong. Solution: make fsks behave more like fmvs: - A flatten-skolem is now a MetaTyVar, whose MetaInfo is FlatSkolTv - We "fill in" that meta-tyvar when leaving the implication - The old FlatSkol form of TcTyVarDetails is gone completely - We track the flatten-skolems for the current implication in a new field of InertSet, inert_fsks. See Note [The flattening story] in TcFlatten. In doing this I found various other things to fix: * I removed the zonkSimples from TcFlatten.unflattenWanteds; it wasn't needed. But I added one in TcSimplify.floatEqualities, which does the zonk precisely when it is needed. * Trac #13674 showed up a case where we had - an insoluble Given, e.g. a ~ [a] - the same insoluble Wanted a ~ [a] We don't use the Given to rewwrite the Wanted (obviously), but we therefore ended up reporting Can't deduce (a ~ [a]) from (a ~ [a]) which is silly. Conclusion: when reporting errors, make the occurs check "win" See Note [Occurs check wins] in TcErrors >--------------------------------------------------------------- 8dc6d645fc3384b3b8ded0578939f5c855dd2ed5 compiler/typecheck/TcCanonical.hs | 2 +- compiler/typecheck/TcErrors.hs | 34 +++-- compiler/typecheck/TcFlatten.hs | 78 ++++++------ compiler/typecheck/TcHsSyn.hs | 1 - compiler/typecheck/TcInteract.hs | 13 +- compiler/typecheck/TcMType.hs | 18 +-- compiler/typecheck/TcRnTypes.hs | 4 +- compiler/typecheck/TcSMonad.hs | 138 ++++++++++++++------- compiler/typecheck/TcSimplify.hs | 23 ++-- compiler/typecheck/TcType.hs | 40 +++--- compiler/typecheck/TcUnify.hs | 1 - testsuite/tests/deriving/should_fail/T7148.stderr | 8 +- testsuite/tests/gadt/T3169.stderr | 6 +- testsuite/tests/gadt/T7558.stderr | 6 +- .../tests/indexed-types/should_fail/T13674.hs | 56 +++++++++ .../tests/indexed-types/should_fail/T13674.stderr | 28 +++++ .../tests/indexed-types/should_fail/T4272.stderr | 7 +- .../tests/indexed-types/should_fail/T9662.stderr | 4 +- testsuite/tests/indexed-types/should_fail/all.T | 1 + .../tests/typecheck/should_compile/FD3.stderr | 6 +- .../tests/typecheck/should_compile/T9834.stderr | 4 +- testsuite/tests/typecheck/should_fail/mc19.stderr | 6 +- testsuite/tests/typecheck/should_fail/mc21.stderr | 6 +- testsuite/tests/typecheck/should_fail/mc22.stderr | 6 +- .../tests/typecheck/should_fail/tcfail191.stderr | 6 +- .../tests/typecheck/should_fail/tcfail193.stderr | 6 +- 26 files changed, 321 insertions(+), 187 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 8dc6d645fc3384b3b8ded0578939f5c855dd2ed5 From git at git.haskell.org Fri May 26 08:55:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 May 2017 08:55:20 +0000 (UTC) Subject: [commit: ghc] master: Make isInsolubleOccursCheck more aggressive (c2eea08) Message-ID: <20170526085520.B07603A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c2eea089e7978416c6882a5456117db27b8f45ba/ghc >--------------------------------------------------------------- commit c2eea089e7978416c6882a5456117db27b8f45ba Author: Simon Peyton Jones Date: Fri May 26 09:27:08 2017 +0100 Make isInsolubleOccursCheck more aggressive Consider type family F a :: * -> * Then (a ~ F Int a) is an insoluble occurs check, and can be reported as such. Previous to this patch, TcType.isInsolubleOccursCheck was treating any type-family application (including an over-saturated one) as unconditionally not-insoluble. This really only affects error messages, and then only slightly. I tripped over this when investigating Trac #13674. >--------------------------------------------------------------- c2eea089e7978416c6882a5456117db27b8f45ba compiler/typecheck/TcType.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index ab2f843..bd72981 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -2152,7 +2152,9 @@ isInsolubleOccursCheck eq_rel tv ty go (CoercionTy _) = False -- ToDo: what about the coercion go (TyConApp tc tys) | isGenerativeTyCon tc role = any go tys - | otherwise = False + | otherwise = any go (drop (tyConArity tc) tys) + -- (a ~ F b a), where F has arity 1, + -- has an insoluble occurs check role = eqRelRole eq_rel From git at git.haskell.org Fri May 26 12:22:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 May 2017 12:22:42 +0000 (UTC) Subject: [commit: ghc] master: Shrink a couple of hs-boot files (226860e) Message-ID: <20170526122242.C00333A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/226860e786ccb2c5660b64c9cf66e58eaf4dc672/ghc >--------------------------------------------------------------- commit 226860e786ccb2c5660b64c9cf66e58eaf4dc672 Author: Simon Peyton Jones Date: Thu May 25 16:07:09 2017 +0100 Shrink a couple of hs-boot files IfaceType.hs-boot and ToIface.hs-boot were bigger than they needed to be, so I'm shrinking them. >--------------------------------------------------------------- 226860e786ccb2c5660b64c9cf66e58eaf4dc672 compiler/iface/IfaceType.hs-boot | 29 ++++++----------------------- compiler/iface/ToIface.hs-boot | 5 ++--- 2 files changed, 8 insertions(+), 26 deletions(-) diff --git a/compiler/iface/IfaceType.hs-boot b/compiler/iface/IfaceType.hs-boot index 2a5331e..4807419 100644 --- a/compiler/iface/IfaceType.hs-boot +++ b/compiler/iface/IfaceType.hs-boot @@ -1,37 +1,20 @@ --- Exists to allow TyCoRep to import pretty-printers -module IfaceType where +-- Used only by ToIface.hs-boot + +module IfaceType( IfaceType, IfaceTyCon, IfaceForAllBndr + , IfaceCoercion, IfaceTyLit, IfaceTcArgs ) where import Var (TyVarBndr, ArgFlag) import TyCon (TyConBndrVis) -import BasicTypes (TyPrec) -import Outputable (Outputable, SDoc) import FastString (FastString) +data IfaceTcArgs type IfLclName = FastString type IfaceKind = IfaceType -type IfacePredType = IfaceType -data ShowForAllFlag data IfaceType data IfaceTyCon data IfaceTyLit data IfaceCoercion -data IfaceTcArgs -type IfaceTvBndr = (IfLclName, IfaceKind) +type IfaceTvBndr = (IfLclName, IfaceKind) type IfaceTyConBinder = TyVarBndr IfaceTvBndr TyConBndrVis type IfaceForAllBndr = TyVarBndr IfaceTvBndr ArgFlag - -instance Outputable IfaceType - -pprIfaceType, pprParendIfaceType :: IfaceType -> SDoc -pprIfaceSigmaType :: ShowForAllFlag -> IfaceType -> SDoc -pprIfaceTyLit :: IfaceTyLit -> SDoc -pprIfaceForAll :: [IfaceForAllBndr] -> SDoc -pprIfaceTvBndr :: Bool -> IfaceTvBndr -> SDoc -pprUserIfaceForAll :: [IfaceForAllBndr] -> SDoc -pprIfaceContext :: [IfacePredType] -> SDoc -pprIfaceContextArr :: [IfacePredType] -> SDoc -pprIfaceTypeApp :: TyPrec -> IfaceTyCon -> IfaceTcArgs -> SDoc -pprIfaceCoTcApp :: TyPrec -> IfaceTyCon -> [IfaceCoercion] -> SDoc -pprTyTcApp :: TyPrec -> IfaceTyCon -> IfaceTcArgs -> SDoc -pprIfacePrefixApp :: TyPrec -> SDoc -> [SDoc] -> SDoc diff --git a/compiler/iface/ToIface.hs-boot b/compiler/iface/ToIface.hs-boot index 04ceab6..f361427 100644 --- a/compiler/iface/ToIface.hs-boot +++ b/compiler/iface/ToIface.hs-boot @@ -1,17 +1,16 @@ module ToIface where import {-# SOURCE #-} TyCoRep -import {-# SOURCE #-} IfaceType +import {-# SOURCE #-} IfaceType( IfaceType, IfaceTyCon, IfaceForAllBndr + , IfaceCoercion, IfaceTyLit, IfaceTcArgs ) import Var ( TyVar, TyVarBinder ) import TyCon ( TyCon ) import VarSet( VarSet ) -- For TyCoRep -toIfaceType :: Type -> IfaceType toIfaceTypeX :: VarSet -> Type -> IfaceType toIfaceTyLit :: TyLit -> IfaceTyLit toIfaceForAllBndr :: TyVarBinder -> IfaceForAllBndr -toIfaceTvBndr :: TyVar -> IfaceTvBndr toIfaceTyCon :: TyCon -> IfaceTyCon toIfaceTcArgs :: TyCon -> [Type] -> IfaceTcArgs toIfaceCoercion :: Coercion -> IfaceCoercion From git at git.haskell.org Fri May 26 12:22:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 May 2017 12:22:45 +0000 (UTC) Subject: [commit: ghc] master: Some tidying up of type pretty-printing (ad14efd) Message-ID: <20170526122245.8F14B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ad14efd539377aaf472ad69449dcaf3e679b0e51/ghc >--------------------------------------------------------------- commit ad14efd539377aaf472ad69449dcaf3e679b0e51 Author: Simon Peyton Jones Date: Thu May 25 16:18:06 2017 +0100 Some tidying up of type pretty-printing Triggered by the changes in #13677, I ended up doing a bit of refactoring in type pretty-printing. * We were using TyOpPrec and FunPrec rather inconsitently, so I made it consisent. * That exposed the fact that we were a bit undecided about whether to print a + b -> c + d vs (a+b) -> (c+d) and similarly a ~ [b] => blah vs (a ~ [b]) => blah I decided to make TyOpPrec and FunPrec compare equal (in BasicTypes), so (->) is treated as equal precedence with other type operators, so you get the unambiguous forms above, even though they have more parens. We could readily reverse this decision. See Note [Type operator precedence] in BasicTypes * I fixed a bug in pretty-printing of HsType where some parens were omitted by mistake. >--------------------------------------------------------------- ad14efd539377aaf472ad69449dcaf3e679b0e51 compiler/basicTypes/BasicTypes.hs | 57 +++++++++++++- compiler/hsSyn/HsTypes.hs | 4 +- compiler/iface/IfaceType.hs | 87 ++++++++++++---------- compiler/typecheck/TcErrors.hs | 2 +- compiler/typecheck/TcType.hs | 2 +- compiler/types/TyCoRep.hs | 32 ++++---- compiler/types/Type.hs | 3 +- .../tests/backpack/should_fail/bkpfail24.stderr | 6 +- testsuite/tests/gadt/T7558.stderr | 2 +- .../tests/generics/T10604/T10604_deriving.stderr | 2 +- testsuite/tests/ghci/scripts/T12024.stdout | 3 +- .../haddock/haddock_examples/haddock.Test.stderr | 22 +++--- .../should_compile_flag_haddock/haddockA023.stderr | 2 +- .../should_compile_flag_haddock/haddockA024.stderr | 2 +- .../should_compile_flag_haddock/haddockA025.stderr | 2 +- .../should_compile_flag_haddock/haddockA026.stderr | 3 +- .../should_compile_flag_haddock/haddockA027.stderr | 4 +- .../should_compile_flag_haddock/haddockA028.stderr | 2 +- .../should_compile/PushedInAsGivens.stderr | 2 +- .../indexed-types/should_compile/Simple14.stderr | 6 +- .../indexed-types/should_fail/SimpleFail15.stderr | 5 +- .../tests/indexed-types/should_fail/T4093a.stderr | 4 +- .../should_compile/DataFamilyInstanceLHS.stderr | 4 +- .../should_compile/EqualityConstraint.stderr | 2 +- .../NamedWildcardInDataFamilyInstanceLHS.stderr | 4 +- testsuite/tests/polykinds/T10503.stderr | 7 +- testsuite/tests/polykinds/T7230.stderr | 2 +- testsuite/tests/polykinds/T7328.stderr | 2 +- testsuite/tests/polykinds/T9222.stderr | 4 +- .../tests/roles/should_compile/Roles13.stderr | 2 +- testsuite/tests/roles/should_compile/Roles3.stderr | 4 +- .../tests/typecheck/should_compile/T10632.stderr | 2 +- .../typecheck/should_fail/ClassOperator.stderr | 8 +- .../typecheck/should_fail/FrozenErrorTests.stderr | 2 +- .../tests/typecheck/should_fail/IPFail.stderr | 2 +- .../tests/typecheck/should_fail/T12921.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5858.stderr | 2 +- .../tests/typecheck/should_fail/T7019a.stderr | 2 +- testsuite/tests/typecheck/should_fail/T7525.stderr | 4 +- testsuite/tests/typecheck/should_fail/T7857.stderr | 2 +- testsuite/tests/typecheck/should_fail/T8912.stderr | 2 +- .../tests/typecheck/should_fail/tcfail041.stderr | 2 +- .../tests/typecheck/should_fail/tcfail211.stderr | 4 +- 43 files changed, 191 insertions(+), 128 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 ad14efd539377aaf472ad69449dcaf3e679b0e51 From git at git.haskell.org Fri May 26 12:50:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 May 2017 12:50:09 +0000 (UTC) Subject: [commit: ghc] master: Typos in comments [ci skip] (19c4203) Message-ID: <20170526125009.B664A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/19c4203f12a849e1d468d7c1de5cd6bfe75a4bc1/ghc >--------------------------------------------------------------- commit 19c4203f12a849e1d468d7c1de5cd6bfe75a4bc1 Author: Gabor Greif Date: Fri May 26 11:08:54 2017 +0200 Typos in comments [ci skip] >--------------------------------------------------------------- 19c4203f12a849e1d468d7c1de5cd6bfe75a4bc1 compiler/llvmGen/Llvm/AbsSyn.hs | 2 +- compiler/main/ErrUtils.hs | 2 +- compiler/typecheck/TcBinds.hs | 2 +- compiler/typecheck/TcErrors.hs | 2 +- compiler/typecheck/TcPatSyn.hs | 2 +- compiler/typecheck/TcSMonad.hs | 4 ++-- compiler/typecheck/TcSimplify.hs | 4 ++-- compiler/typecheck/TcUnify.hs | 6 +++--- 8 files changed, 12 insertions(+), 12 deletions(-) diff --git a/compiler/llvmGen/Llvm/AbsSyn.hs b/compiler/llvmGen/Llvm/AbsSyn.hs index 45d79f5..8f38c79 100644 --- a/compiler/llvmGen/Llvm/AbsSyn.hs +++ b/compiler/llvmGen/Llvm/AbsSyn.hs @@ -267,7 +267,7 @@ data LlvmExpression {- | Cast the variable from to the to type. This is an abstraction of three - cast operators in Llvm, inttoptr, prttoint and bitcast. + cast operators in Llvm, inttoptr, ptrtoint and bitcast. * cast: Cast type * from: Variable to cast * to: type to cast to diff --git a/compiler/main/ErrUtils.hs b/compiler/main/ErrUtils.hs index 40f6648..64d23c7 100644 --- a/compiler/main/ErrUtils.hs +++ b/compiler/main/ErrUtils.hs @@ -153,7 +153,7 @@ data Severity | SevInteractive | SevDump - -- ^ Log messagse intended for compiler developers + -- ^ Log message intended for compiler developers -- No file/line/column stuff | SevInfo diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index 70e444e..ec8f235 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -1619,7 +1619,7 @@ decideGeneralisationPlan dflags lbinds closed sig_fn binds = map unLoc lbinds partial_sig_mrs :: [Bool] - -- One for each parital signature (so empty => no partial sigs) + -- One for each partial signature (so empty => no partial sigs) -- The Bool is True if the signature has no constraint context -- so we should apply the MR -- See Note [Partial type signatures and generalisation] diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index 6d422a4..324391f 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -2035,7 +2035,7 @@ Conclusion: if there's an insoluble occurs check (isInsolubleOccursCheck) then report it first. (NB: there are potentially-soluble ones, like (a ~ F a b), and we don't -wnat to be as draconian with them.) +want to be as draconian with them.) Note [Expanding type synonyms to make types similar] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index dc2c4de..6d2426f 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -208,7 +208,7 @@ Consider pattern P x <- MkT x This should work. But in the matcher we must match against MkT, and then -instantiate its argument 'x', to get a functino of type (Int -> Int). +instantiate its argument 'x', to get a function of type (Int -> Int). Equality is not enough! Trac #13752 was an example. Note [Checking against a pattern signature] diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index 434553d..bb305ed 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -2837,7 +2837,7 @@ unflattenGivens :: IORef InertSet -> TcM () -- NB: this is the /only/ way that a fsk (MetaDetails = FlatSkolTv) -- is filled in. Nothing else does so. -- --- It's here (rather than in TcFlatten) becuause the Right Places +-- It's here (rather than in TcFlatten) because the Right Places -- to call it are in runTcSWithEvBinds/nestImplicTcS, where it -- is nicely paired with the creation an empty inert_fsks list. unflattenGivens inert_var @@ -2885,7 +2885,7 @@ demoteUnfilledFmv fmv {- ********************************************************************* * * -* Instantaiation etc +* Instantiation etc. * * ********************************************************************* -} diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index a611198..dcb146a 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -926,7 +926,7 @@ defaultTyVarsAndSimplify rhs_tclvl mono_tvs candidates decideQuantifiedTyVars :: TyCoVarSet -- Monomorphic tyvars -> [(Name,TcType)] -- Annotated theta and (name,tau) pairs - -> [TcIdSigInst] -- Parital signatures + -> [TcIdSigInst] -- Partial signatures -> [PredType] -- Candidates, zonked -> TcM [TyVar] -- Fix what tyvars we are going to quantify over, and quantify them @@ -1955,7 +1955,7 @@ floatEqualities skols no_given_eqs = return (emptyBag, wanteds) -- Note [Float Equalities out of Implications] | otherwise - = do { -- First zonk: the inert set (from whence they came) are is fully + = do { -- First zonk: the inert set (from whence they came) is fully -- zonked, but unflattening may have filled in unification -- variables, and we /must/ see them. Otherwise we may float -- constraints that mention the skolems! diff --git a/compiler/typecheck/TcUnify.hs b/compiler/typecheck/TcUnify.hs index 3f1d77a..f106268 100644 --- a/compiler/typecheck/TcUnify.hs +++ b/compiler/typecheck/TcUnify.hs @@ -687,7 +687,7 @@ So roughly: (i.e. skolemisation is the next thing we'd do) * and the ty_actual has no top-level polymorphism (but looking deeply) then we can revert to simple equality. But we need to be careful. -These examples are allfine: +These examples are all fine: * (Char -> forall a. a->a) <= (forall a. Char -> a -> a) Polymorphism is buried in ty_actual @@ -703,8 +703,8 @@ These examples are allfine: ty_expected isn't really polymorphic If we prematurely go to equality we'll reject a program we should -accept (e.g. Grac #13752). So the test (which is only to improve -error messagse) is very conservative: +accept (e.g. Trac #13752). So the test (which is only to improve +error message) is very conservative: * ty_actual is /definitely/ monomorphic * ty_expected is /definitely/ polymorphic -} From git at git.haskell.org Fri May 26 15:07:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 May 2017 15:07:21 +0000 (UTC) Subject: [commit: ghc] branch 'wip/new-tree-one-param-2' created Message-ID: <20170526150721.C2D7B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/new-tree-one-param-2 Referencing: 13e61fe7ef79580ce6767126fe536846f83163f1 From git at git.haskell.org Fri May 26 15:07:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 May 2017 15:07:25 +0000 (UTC) Subject: [commit: ghc] wip/new-tree-one-param-2: Udate hsSyn AST to use Trees that Grow (13e61fe) Message-ID: <20170526150725.505113A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-tree-one-param-2 Link : http://ghc.haskell.org/trac/ghc/changeset/13e61fe7ef79580ce6767126fe536846f83163f1/ghc >--------------------------------------------------------------- commit 13e61fe7ef79580ce6767126fe536846f83163f1 Author: Alan Zimmerman Date: Fri May 19 14:56:09 2017 +0200 Udate hsSyn AST to use Trees that Grow Summary: See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow This commit prepares the ground for a full extensible AST, by replacing the type parameter for the hsSyn data types with a set of indices into type families, data GhcPs -- ^ Index for GHC parser output data GhcRn -- ^ Index for GHC renamer output data GhcTc -- ^ Index for GHC typechecker output These are now used instead of `RdrName`, `Name` and `Id`/`TcId`/`Var` Where the original name type is required in a polymorphic context, this is accessible via the IdP type family, defined as type family IdP p type instance IdP GhcPs = RdrName type instance IdP GhcRn = Name type instance IdP GhcTc = Id These types are declared in the new 'hsSyn/HsExtension.hs' module. To gain a better understanding of the extension mechanism, it has been applied to `HsLit` only, also replacing the `SourceText` fields in them with extension types. To preserve extension generality, a type class is introduced to capture the `SourceText` interface, which must be honoured by all of the extension points which originally had a `SourceText`. The class is defined as class HasSourceText a where -- Provide setters to mimic existing constructors noSourceText :: a sourceText :: String -> a setSourceText :: SourceText -> a getSourceText :: a -> SourceText And the constraint is captured in `SourceTextX`, which is a constraint type listing all the extension points that make use of the class. Updating Haddock submodule to match. Test Plan: ./validate Reviewers: simonpj, shayan-najd, goldfire, austin, bgamari Subscribers: rwbarton, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D3609 >--------------------------------------------------------------- 13e61fe7ef79580ce6767126fe536846f83163f1 compiler/backpack/BkpSyn.hs | 3 +- compiler/backpack/DriverBkp.hs | 4 +- compiler/deSugar/Check.hs | 64 +-- compiler/deSugar/Coverage.hs | 121 ++--- compiler/deSugar/Desugar.hs | 7 +- compiler/deSugar/DsArrows.hs | 70 +-- compiler/deSugar/DsBinds.hs | 16 +- compiler/deSugar/DsExpr.hs | 41 +- compiler/deSugar/DsExpr.hs-boot | 16 +- compiler/deSugar/DsForeign.hs | 10 +- compiler/deSugar/DsGRHSs.hs | 18 +- compiler/deSugar/DsListComp.hs | 59 +-- compiler/deSugar/DsMeta.hs | 226 ++++----- compiler/deSugar/DsMonad.hs | 2 +- compiler/deSugar/DsUtils.hs | 29 +- compiler/deSugar/Match.hs | 43 +- compiler/deSugar/Match.hs-boot | 9 +- compiler/deSugar/MatchCon.hs | 7 +- compiler/deSugar/MatchLit.hs | 38 +- compiler/deSugar/PmExpr.hs | 12 +- compiler/ghc.cabal.in | 1 + compiler/ghc.mk | 1 + compiler/hsSyn/Convert.hs | 147 +++--- compiler/hsSyn/HsBinds.hs | 121 ++--- compiler/hsSyn/HsDecls.hs | 513 +++++++++++---------- compiler/hsSyn/HsDumpAst.hs | 28 +- compiler/hsSyn/HsExpr.hs | 458 +++++++++--------- compiler/hsSyn/HsExpr.hs-boot | 40 +- compiler/hsSyn/HsExtension.hs | 303 ++++++++++++ compiler/hsSyn/HsImpExp.hs | 37 +- compiler/hsSyn/HsLit.hs | 131 ++++-- compiler/hsSyn/HsPat.hs | 168 +++---- compiler/hsSyn/HsPat.hs-boot | 6 +- compiler/hsSyn/HsSyn.hs | 7 +- compiler/hsSyn/HsTypes.hs | 384 +++++++-------- compiler/hsSyn/HsUtils.hs | 296 ++++++------ compiler/hsSyn/PlaceHolder.hs | 50 -- compiler/main/GHC.hs | 8 +- compiler/main/HeaderInfo.hs | 7 +- compiler/main/Hooks.hs | 13 +- compiler/main/HscMain.hs | 16 +- compiler/main/HscStats.hs | 3 +- compiler/main/HscTypes.hs | 34 +- compiler/main/InteractiveEval.hs | 10 +- compiler/parser/Parser.y | 373 +++++++-------- compiler/parser/RdrHsSyn.hs | 243 +++++----- compiler/rename/RnBinds.hs | 147 +++--- compiler/rename/RnEnv.hs | 29 +- compiler/rename/RnExpr.hs | 221 ++++----- compiler/rename/RnExpr.hs-boot | 22 +- compiler/rename/RnFixity.hs | 2 +- compiler/rename/RnNames.hs | 85 ++-- compiler/rename/RnPat.hs | 63 +-- compiler/rename/RnSource.hs | 181 ++++---- compiler/rename/RnSplice.hs | 50 +- compiler/rename/RnSplice.hs-boot | 12 +- compiler/rename/RnTypes.hs | 209 ++++----- compiler/rename/RnUtils.hs | 2 +- compiler/typecheck/Inst.hs | 29 +- compiler/typecheck/TcAnnotations.hs | 17 +- compiler/typecheck/TcArrows.hs | 19 +- compiler/typecheck/TcBackpack.hs | 1 + compiler/typecheck/TcBinds.hs | 94 ++-- compiler/typecheck/TcClassDcl.hs | 41 +- compiler/typecheck/TcDefaults.hs | 8 +- compiler/typecheck/TcDeriv.hs | 39 +- compiler/typecheck/TcDerivUtils.hs | 8 +- compiler/typecheck/TcEnv.hs | 18 +- compiler/typecheck/TcEnv.hs-boot | 1 + compiler/typecheck/TcExpr.hs | 142 +++--- compiler/typecheck/TcExpr.hs-boot | 31 +- compiler/typecheck/TcForeign.hs | 19 +- compiler/typecheck/TcGenDeriv.hs | 144 +++--- compiler/typecheck/TcGenFunctor.hs | 99 ++-- compiler/typecheck/TcGenGenerics.hs | 32 +- compiler/typecheck/TcHsSyn.hs | 135 +++--- compiler/typecheck/TcHsType.hs | 92 ++-- compiler/typecheck/TcInstDcls.hs | 70 +-- compiler/typecheck/TcInstDcls.hs-boot | 4 +- compiler/typecheck/TcMatches.hs | 95 ++-- compiler/typecheck/TcMatches.hs-boot | 11 +- compiler/typecheck/TcPat.hs | 53 +-- compiler/typecheck/TcPatSyn.hs | 84 ++-- compiler/typecheck/TcPatSyn.hs-boot | 13 +- compiler/typecheck/TcRnDriver.hs | 59 +-- compiler/typecheck/TcRnExports.hs | 41 +- compiler/typecheck/TcRnTypes.hs | 72 +-- compiler/typecheck/TcRules.hs | 10 +- compiler/typecheck/TcSigs.hs | 34 +- compiler/typecheck/TcSplice.hs | 51 +- compiler/typecheck/TcSplice.hs-boot | 36 +- compiler/typecheck/TcTyClsDecls.hs | 111 ++--- compiler/typecheck/TcTyDecls.hs | 11 +- compiler/typecheck/TcTypeable.hs | 55 +-- compiler/typecheck/TcUnify.hs | 11 +- compiler/typecheck/TcUnify.hs-boot | 14 +- compiler/typecheck/TcValidity.hs | 2 +- ghc/GHCi/UI.hs | 6 +- ghc/GHCi/UI/Info.hs | 6 +- ghc/GHCi/UI/Monad.hs | 7 +- .../tests/ghc-api/annotations-literals/parsed.hs | 6 +- testsuite/tests/ghc-api/annotations/parseTree.hs | 2 +- .../tests/ghc-api/annotations/stringSource.hs | 6 +- testsuite/tests/ghc-api/annotations/t11430.hs | 4 +- testsuite/tests/quasiquotation/T7918.hs | 6 +- utils/ghctags/Main.hs | 5 +- utils/haddock | 2 +- 107 files changed, 3778 insertions(+), 3294 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 13e61fe7ef79580ce6767126fe536846f83163f1 From git at git.haskell.org Fri May 26 22:28:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 May 2017 22:28:09 +0000 (UTC) Subject: [commit: ghc] master: Revert "Rewrite boot in Python" (7fce4cb) Message-ID: <20170526222809.4332F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7fce4cbc0e0d00352826c5ef1d7f6bf8dbb826b9/ghc >--------------------------------------------------------------- commit 7fce4cbc0e0d00352826c5ef1d7f6bf8dbb826b9 Author: Ben Gamari Date: Fri May 26 18:27:37 2017 -0400 Revert "Rewrite boot in Python" This reverts commit 0440af6abe592c2366d302d603664fe763ad0828. Unfortunately this breaks on Windows for tiresome reasons. I'll need to reevaluate this. >--------------------------------------------------------------- 7fce4cbc0e0d00352826c5ef1d7f6bf8dbb826b9 INSTALL.md | 8 +- MAKEHELP.md | 2 +- boot | 385 +++++++++++++++++++++++++++++++++++------------------------ configure.ac | 2 +- validate | 4 +- 5 files changed, 236 insertions(+), 165 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 7fce4cbc0e0d00352826c5ef1d7f6bf8dbb826b9 From git at git.haskell.org Fri May 26 22:49:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 May 2017 22:49:11 +0000 (UTC) Subject: [commit: ghc] master: Add regression test for #13758 (c823140) Message-ID: <20170526224911.48E1B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c82314085f2721915ea143a53f09de111aee7edb/ghc >--------------------------------------------------------------- commit c82314085f2721915ea143a53f09de111aee7edb Author: Ryan Scott Date: Fri May 26 18:47:28 2017 -0400 Add regression test for #13758 >--------------------------------------------------------------- c82314085f2721915ea143a53f09de111aee7edb testsuite/tests/deriving/should_compile/T13758.hs | 57 +++++++++++++++++++++++ testsuite/tests/deriving/should_compile/all.T | 1 + 2 files changed, 58 insertions(+) diff --git a/testsuite/tests/deriving/should_compile/T13758.hs b/testsuite/tests/deriving/should_compile/T13758.hs new file mode 100644 index 0000000..91ddd99 --- /dev/null +++ b/testsuite/tests/deriving/should_compile/T13758.hs @@ -0,0 +1,57 @@ +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# Language ScopedTypeVariables #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE UndecidableInstances #-} +module T13758 where + +import Data.Coerce +import GHC.Generics +import Data.Semigroup + +----- + +class Monoid' f where + mempty' :: f x + mappend' :: f x -> f x -> f x + +instance Monoid' U1 where + mempty' = U1 + mappend' U1 U1 = U1 + +instance Monoid a => Monoid' (K1 i a) where + mempty' = K1 mempty + mappend' (K1 x) (K1 y) = K1 (x `mappend` y) + +instance Monoid' f => Monoid' (M1 i c f) where + mempty' = M1 mempty' + mappend' (M1 x) (M1 y) = M1 (x `mappend'` y) + +instance (Monoid' f, Monoid' h) => Monoid' (f :*: h) where + mempty' = mempty' :*: mempty' + mappend' (x1 :*: y1) (x2 :*: y2) = mappend' x1 x2 :*: mappend' y1 y2 + +memptydefault :: (Generic a, Monoid' (Rep a)) => a +memptydefault = to mempty' + +mappenddefault :: (Generic a, Monoid' (Rep a)) => a -> a -> a +mappenddefault x y = to (mappend' (from x) (from y)) + +----- + +newtype GenericMonoid a = GenericMonoid a + +instance (Generic a, Monoid' (Rep a)) => Semigroup (GenericMonoid a) where + (<>) = coerce (mappenddefault :: a -> a -> a) + +instance (Generic a, Monoid' (Rep a)) => Monoid (GenericMonoid a) where + mempty = coerce (memptydefault :: a) + mappend = coerce (mappenddefault :: a -> a -> a) + +data Urls = Urls String String String + deriving (Show, Generic) + +newtype UrlsDeriv = UD (GenericMonoid Urls) + deriving (Semigroup, Monoid) diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T index 837bb04..36476d5 100644 --- a/testsuite/tests/deriving/should_compile/all.T +++ b/testsuite/tests/deriving/should_compile/all.T @@ -88,5 +88,6 @@ test('T12814', normal, compile, ['-Wredundant-constraints']) test('T13272', normal, compile, ['']) test('T13272a', normal, compile, ['']) test('T13297', normal, compile, ['']) +test('T13758', normal, compile, ['']) test('drv-empty-data', [normalise_errmsg_fun(just_the_deriving)],compile, ['-ddump-deriv -dsuppress-uniques']) test('drv-phantom', [normalise_errmsg_fun(just_the_deriving)],compile, ['-ddump-deriv -dsuppress-uniques']) From git at git.haskell.org Sat May 27 01:29:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 May 2017 01:29:37 +0000 (UTC) Subject: [commit: ghc] master: Add regression test for #12648 (27f6f38) Message-ID: <20170527012937.62A393A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/27f6f388ef1a3cd694008150fe513e3e7be2e6ad/ghc >--------------------------------------------------------------- commit 27f6f388ef1a3cd694008150fe513e3e7be2e6ad Author: Ryan Scott Date: Fri May 26 21:28:28 2017 -0400 Add regression test for #12648 Commit ce97b7298d54bdfccd9dcf366a69c5617b4eb43f (the fix for #12175) also fixed #12648. Let's add a regression test so that it stays fixed. >--------------------------------------------------------------- 27f6f388ef1a3cd694008150fe513e3e7be2e6ad testsuite/tests/typecheck/should_fail/T12648.hs | 76 ++++++++++++++++++++++ .../tests/typecheck/should_fail/T12648.stderr | 17 +++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 94 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T12648.hs b/testsuite/tests/typecheck/should_fail/T12648.hs new file mode 100644 index 0000000..b36ecce --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T12648.hs @@ -0,0 +1,76 @@ +{-# LANGUAGE ConstraintKinds #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE FunctionalDependencies #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE UndecidableSuperClasses #-} +module T12648 where + +import GHC.Exts (Constraint) +import Unsafe.Coerce (unsafeCoerce) + +type family Skolem (p :: k -> Constraint) :: k +type family Forall (p :: k -> Constraint) :: Constraint +type instance Forall p = Forall_ p +class p (Skolem p) => Forall_ (p :: k -> Constraint) +instance p (Skolem p) => Forall_ (p :: k -> Constraint) + +inst :: forall p a. Forall p :- p a +inst = unsafeCoerce (Sub Dict :: Forall p :- p (Skolem p)) + +data Dict :: Constraint -> * where + Dict :: a => Dict a + +newtype a :- b = Sub (a => Dict b) + +infixl 1 \\ -- required comment + +(\\) :: a => (b => r) -> (a :- b) -> r +r \\ Sub Dict = r + +class (Applicative b, Applicative m, Monad b, Monad m) => MonadBase b m | m -> b + +instance MonadBase IO IO -- where liftBase = id + +class MonadBase b m => MonadBaseControl b m | m -> b where + type StM m a :: * + liftBaseWith :: (RunInBase m b -> b a) -> m a + +type RunInBase m b = forall a. m a -> b (StM m a) + +instance MonadBaseControl IO IO where + type StM IO a = a + liftBaseWith f = f id + {-# INLINABLE liftBaseWith #-} + +class (StM m a ~ a) => IdenticalBase m a +instance (StM m a ~ a) => IdenticalBase m a + +newtype UnliftBase b m = UnliftBase { unliftBase :: forall a. m a -> b a } + +mkUnliftBase :: forall m a b. (Forall (IdenticalBase m), Monad b) + => (forall c. m c -> b (StM m c)) -> m a -> b a +mkUnliftBase r act = r act \\ (inst :: Forall (IdenticalBase m) :- IdenticalBase m a) + +class (MonadBaseControl b m, Forall (IdenticalBase m)) => MonadBaseUnlift b m | m -> b +instance (MonadBaseControl b m, Forall (IdenticalBase m)) => MonadBaseUnlift b m + +askUnliftBase :: forall b m. (MonadBaseUnlift b m) => m (UnliftBase b m) +askUnliftBase = liftBaseWith unlifter + where + unlifter :: (forall c. m c -> b (StM m c)) -> b (UnliftBase b m) + unlifter r = return $ UnliftBase (mkUnliftBase r) + +f :: (MonadBaseUnlift m IO) => m a +f = do + + _ <- askUnliftBase + + return () diff --git a/testsuite/tests/typecheck/should_fail/T12648.stderr b/testsuite/tests/typecheck/should_fail/T12648.stderr new file mode 100644 index 0000000..227bc67 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T12648.stderr @@ -0,0 +1,17 @@ + +T12648.hs:76:2: error: + • Couldn't match type ‘a’ with ‘()’ + ‘a’ is a rigid type variable bound by + the type signature for: + f :: forall (m :: * -> *) a. MonadBaseUnlift m IO => m a + at T12648.hs:71:1-34 + Expected type: m a + Actual type: m () + • In a stmt of a 'do' block: return () + In the expression: + do _ <- askUnliftBase + return () + In an equation for ‘f’: + f = do _ <- askUnliftBase + return () + • Relevant bindings include f :: m a (bound at T12648.hs:72:1) diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index cf2c3c8..bf4854f 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -415,6 +415,7 @@ test('T12170a', normal, compile_fail, ['']) test('T12124', normal, compile_fail, ['']) test('T12589', normal, compile_fail, ['']) test('T12529', normal, compile_fail, ['']) +test('T12648', normal, compile_fail, ['']) test('T12729', normal, compile_fail, ['']) test('T12785b', normal, compile_fail, ['']) test('T12803', normal, compile_fail, ['']) From git at git.haskell.org Sat May 27 04:55:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 May 2017 04:55:39 +0000 (UTC) Subject: [commit: ghc] master: user-guide: Add since annotation for -Wcpp-undef (52fe138) Message-ID: <20170527045539.408C53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/52fe138ef7fb23554c7af996a0aa1f641082d275/ghc >--------------------------------------------------------------- commit 52fe138ef7fb23554c7af996a0aa1f641082d275 Author: Erik de Castro Lopo Date: Sat May 27 14:54:42 2017 +1000 user-guide: Add since annotation for -Wcpp-undef Reviewers: hvr, bgamari, austin Reviewed By: hvr Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3612 >--------------------------------------------------------------- 52fe138ef7fb23554c7af996a0aa1f641082d275 docs/users_guide/using-warnings.rst | 2 ++ 1 file changed, 2 insertions(+) diff --git a/docs/users_guide/using-warnings.rst b/docs/users_guide/using-warnings.rst index 6a42f54..9bc1c35 100644 --- a/docs/users_guide/using-warnings.rst +++ b/docs/users_guide/using-warnings.rst @@ -1033,6 +1033,8 @@ of ``-W(no-)*``. .. ghc-flag:: -Wcpp-undef + :since: 8.2 + This flag passes ``-Wundef`` to the C pre-processor (if its being used) which causes the pre-processor to warn on uses of the `#if` directive on undefined identifiers. From git at git.haskell.org Sat May 27 10:02:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 May 2017 10:02:41 +0000 (UTC) Subject: [commit: ghc] master: template-haskell: Properly escape StrTyLit doc (db1fd97) Message-ID: <20170527100241.0F81D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/db1fd9777525212cf1e563d54491505c4795a7e9/ghc >--------------------------------------------------------------- commit db1fd9777525212cf1e563d54491505c4795a7e9 Author: Eric Mertens Date: Thu May 25 16:44:18 2017 -0700 template-haskell: Properly escape StrTyLit doc >--------------------------------------------------------------- db1fd9777525212cf1e563d54491505c4795a7e9 libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 31e5ccd..2b99a7a 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -1959,7 +1959,7 @@ data InjectivityAnn = InjectivityAnn Name [Name] deriving ( Show, Eq, Ord, Data, Generic ) data TyLit = NumTyLit Integer -- ^ @2@ - | StrTyLit String -- ^ @"Hello"@ + | StrTyLit String -- ^ @\"Hello\"@ deriving ( Show, Eq, Ord, Data, Generic ) -- | Role annotations From git at git.haskell.org Sat May 27 13:11:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 May 2017 13:11:10 +0000 (UTC) Subject: [commit: ghc] master: Fix build after 'Shrink a couple of hs-boot files' (2944d27) Message-ID: <20170527131110.5357D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2944d27d11b84fb104326ed81c5922548a9edb32/ghc >--------------------------------------------------------------- commit 2944d27d11b84fb104326ed81c5922548a9edb32 Author: Bartosz Nitka Date: Sat May 27 06:06:16 2017 -0700 Fix build after 'Shrink a couple of hs-boot files' >--------------------------------------------------------------- 2944d27d11b84fb104326ed81c5922548a9edb32 compiler/iface/IfaceType.hs-boot | 2 -- compiler/iface/ToIface.hs-boot | 2 +- 2 files changed, 1 insertion(+), 3 deletions(-) diff --git a/compiler/iface/IfaceType.hs-boot b/compiler/iface/IfaceType.hs-boot index 4807419..7488aa5 100644 --- a/compiler/iface/IfaceType.hs-boot +++ b/compiler/iface/IfaceType.hs-boot @@ -4,7 +4,6 @@ module IfaceType( IfaceType, IfaceTyCon, IfaceForAllBndr , IfaceCoercion, IfaceTyLit, IfaceTcArgs ) where import Var (TyVarBndr, ArgFlag) -import TyCon (TyConBndrVis) import FastString (FastString) data IfaceTcArgs @@ -16,5 +15,4 @@ data IfaceTyCon data IfaceTyLit data IfaceCoercion type IfaceTvBndr = (IfLclName, IfaceKind) -type IfaceTyConBinder = TyVarBndr IfaceTvBndr TyConBndrVis type IfaceForAllBndr = TyVarBndr IfaceTvBndr ArgFlag diff --git a/compiler/iface/ToIface.hs-boot b/compiler/iface/ToIface.hs-boot index f361427..e2431b8 100644 --- a/compiler/iface/ToIface.hs-boot +++ b/compiler/iface/ToIface.hs-boot @@ -3,7 +3,7 @@ module ToIface where import {-# SOURCE #-} TyCoRep import {-# SOURCE #-} IfaceType( IfaceType, IfaceTyCon, IfaceForAllBndr , IfaceCoercion, IfaceTyLit, IfaceTcArgs ) -import Var ( TyVar, TyVarBinder ) +import Var ( TyVarBinder ) import TyCon ( TyCon ) import VarSet( VarSet ) From git at git.haskell.org Sat May 27 14:45:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 May 2017 14:45:01 +0000 (UTC) Subject: [commit: ghc] master: Fix test output after 'Some tidying up of type pretty-printing' (09d5c99) Message-ID: <20170527144501.BC4AE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/09d5c993aae208e3d34a9e715297922b6ea42b3f/ghc >--------------------------------------------------------------- commit 09d5c993aae208e3d34a9e715297922b6ea42b3f Author: Bartosz Nitka Date: Sat May 27 07:42:26 2017 -0700 Fix test output after 'Some tidying up of type pretty-printing' Most are cosmetic. There's an interesting change in T7861, but the error is still accurate. >--------------------------------------------------------------- 09d5c993aae208e3d34a9e715297922b6ea42b3f testsuite/tests/typecheck/should_run/T7861.stderr | 6 +----- testsuite/tests/typecheck/should_run/Typeable1.stderr | 2 +- testsuite/tests/typecheck/should_run/tcrun045.stderr | 6 +++--- 3 files changed, 5 insertions(+), 9 deletions(-) diff --git a/testsuite/tests/typecheck/should_run/T7861.stderr b/testsuite/tests/typecheck/should_run/T7861.stderr index e9ee5e9..4a1c030 100644 --- a/testsuite/tests/typecheck/should_run/T7861.stderr +++ b/testsuite/tests/typecheck/should_run/T7861.stderr @@ -1,9 +1,5 @@ T7861: T7861.hs:10:5: error: - • Couldn't match type ‘a’ with ‘[a]’ - ‘a’ is a rigid type variable bound by - the type signature for: - f :: forall a. (forall b. a) -> a - at T7861.hs:9:1-23 + • Occurs check: cannot construct the infinite type: a ~ [a] Expected type: (forall b. a) -> a Actual type: (forall b. a) -> [a] • In the expression: doA diff --git a/testsuite/tests/typecheck/should_run/Typeable1.stderr b/testsuite/tests/typecheck/should_run/Typeable1.stderr index 9a7d3b7..65f6fd4 100644 --- a/testsuite/tests/typecheck/should_run/Typeable1.stderr +++ b/testsuite/tests/typecheck/should_run/Typeable1.stderr @@ -7,7 +7,7 @@ Typeable1.hs:22:5: error: App :: forall k2 (t :: k2). () => forall k1 (a :: k1 -> k2) (b :: k1). - t ~ a b => + (t ~ a b) => TypeRep a -> TypeRep b -> TypeRep t, in a pattern binding in 'do' block diff --git a/testsuite/tests/typecheck/should_run/tcrun045.stderr b/testsuite/tests/typecheck/should_run/tcrun045.stderr index 19fca10..f6b1652 100644 --- a/testsuite/tests/typecheck/should_run/tcrun045.stderr +++ b/testsuite/tests/typecheck/should_run/tcrun045.stderr @@ -1,18 +1,18 @@ tcrun045.hs:11:10: error: • Illegal implicit parameter ‘?imp::Int’ - • In the context: (?imp::Int) + • In the context: ?imp::Int While checking an instance declaration In the instance declaration for ‘C Int’ tcrun045.hs:24:1: error: • Illegal implicit parameter ‘?imp::Int’ - • In the context: (?imp::Int) + • In the context: ?imp::Int While checking the super-classes of class ‘D’ In the class declaration for ‘D’ tcrun045.hs:27:10: error: • Illegal implicit parameter ‘?imp::Int’ - • In the context: (?imp::Int) + • In the context: ?imp::Int While checking an instance declaration In the instance declaration for ‘D Int’ From git at git.haskell.org Sun May 28 10:54:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 28 May 2017 10:54:14 +0000 (UTC) Subject: [commit: ghc] master: Remove HsContext from ppr_mono_ty, and remove ppParendHsType (3b23f68) Message-ID: <20170528105414.ACAB13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3b23f680c2b1f80b693eb8896fb21e4bbf8edc7e/ghc >--------------------------------------------------------------- commit 3b23f680c2b1f80b693eb8896fb21e4bbf8edc7e Author: Alan Zimmerman Date: Fri May 26 17:06:11 2017 +0200 Remove HsContext from ppr_mono_ty, and remove ppParendHsType This is a cleanup after Trac #13238, as the context was no longer being used. >--------------------------------------------------------------- 3b23f680c2b1f80b693eb8896fb21e4bbf8edc7e compiler/hsSyn/Convert.hs | 6 +- compiler/hsSyn/HsDecls.hs | 8 +- compiler/hsSyn/HsExpr.hs | 2 +- compiler/hsSyn/HsTypes.hs | 114 ++++++++++----------- compiler/typecheck/TcExpr.hs | 2 +- compiler/typecheck/TcInstDcls.hs | 3 +- .../haddock/haddock_examples/haddock.Test.stderr | 22 ++-- .../should_compile_flag_haddock/haddockA023.stderr | 2 +- .../should_compile_flag_haddock/haddockA024.stderr | 2 +- .../should_compile_flag_haddock/haddockA025.stderr | 2 +- .../should_compile_flag_haddock/haddockA026.stderr | 2 +- .../should_compile_flag_haddock/haddockA027.stderr | 4 +- .../should_compile_flag_haddock/haddockA028.stderr | 2 +- .../indexed-types/should_compile/Simple14.stderr | 2 +- .../indexed-types/should_fail/SimpleFail15.stderr | 2 +- testsuite/tests/polykinds/T10503.stderr | 3 +- testsuite/tests/polykinds/T7328.stderr | 2 +- 17 files changed, 89 insertions(+), 91 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 3b23f680c2b1f80b693eb8896fb21e4bbf8edc7e From git at git.haskell.org Sun May 28 13:23:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 28 May 2017 13:23:11 +0000 (UTC) Subject: [commit: ghc] wip/new-tree-one-param-2: Udate hsSyn AST to use Trees that Grow (e511e8e) Message-ID: <20170528132311.6EAB83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-tree-one-param-2 Link : http://ghc.haskell.org/trac/ghc/changeset/e511e8e1dc4d74bfab6b9fa7acd327082f459119/ghc >--------------------------------------------------------------- commit e511e8e1dc4d74bfab6b9fa7acd327082f459119 Author: Alan Zimmerman Date: Fri May 19 14:56:09 2017 +0200 Udate hsSyn AST to use Trees that Grow Summary: See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow This commit prepares the ground for a full extensible AST, by replacing the type parameter for the hsSyn data types with a set of indices into type families, data GhcPs -- ^ Index for GHC parser output data GhcRn -- ^ Index for GHC renamer output data GhcTc -- ^ Index for GHC typechecker output These are now used instead of `RdrName`, `Name` and `Id`/`TcId`/`Var` Where the original name type is required in a polymorphic context, this is accessible via the IdP type family, defined as type family IdP p type instance IdP GhcPs = RdrName type instance IdP GhcRn = Name type instance IdP GhcTc = Id These types are declared in the new 'hsSyn/HsExtension.hs' module. To gain a better understanding of the extension mechanism, it has been applied to `HsLit` only, also replacing the `SourceText` fields in them with extension types. To preserve extension generality, a type class is introduced to capture the `SourceText` interface, which must be honoured by all of the extension points which originally had a `SourceText`. The class is defined as class HasSourceText a where -- Provide setters to mimic existing constructors noSourceText :: a sourceText :: String -> a setSourceText :: SourceText -> a getSourceText :: a -> SourceText And the constraint is captured in `SourceTextX`, which is a constraint type listing all the extension points that make use of the class. Updating Haddock submodule to match. Test Plan: ./validate Reviewers: simonpj, shayan-najd, goldfire, austin, bgamari Subscribers: rwbarton, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D3609 >--------------------------------------------------------------- e511e8e1dc4d74bfab6b9fa7acd327082f459119 compiler/backpack/BkpSyn.hs | 3 +- compiler/backpack/DriverBkp.hs | 4 +- compiler/deSugar/Check.hs | 64 +-- compiler/deSugar/Coverage.hs | 121 ++--- compiler/deSugar/Desugar.hs | 7 +- compiler/deSugar/DsArrows.hs | 70 +-- compiler/deSugar/DsBinds.hs | 16 +- compiler/deSugar/DsExpr.hs | 41 +- compiler/deSugar/DsExpr.hs-boot | 16 +- compiler/deSugar/DsForeign.hs | 10 +- compiler/deSugar/DsGRHSs.hs | 18 +- compiler/deSugar/DsListComp.hs | 59 +-- compiler/deSugar/DsMeta.hs | 226 ++++----- compiler/deSugar/DsMonad.hs | 2 +- compiler/deSugar/DsUtils.hs | 29 +- compiler/deSugar/Match.hs | 43 +- compiler/deSugar/Match.hs-boot | 9 +- compiler/deSugar/MatchCon.hs | 7 +- compiler/deSugar/MatchLit.hs | 38 +- compiler/deSugar/PmExpr.hs | 12 +- compiler/ghc.cabal.in | 1 + compiler/ghc.mk | 1 + compiler/hsSyn/Convert.hs | 147 +++--- compiler/hsSyn/HsBinds.hs | 121 ++--- compiler/hsSyn/HsDecls.hs | 513 +++++++++++---------- compiler/hsSyn/HsDumpAst.hs | 28 +- compiler/hsSyn/HsExpr.hs | 458 +++++++++--------- compiler/hsSyn/HsExpr.hs-boot | 40 +- compiler/hsSyn/HsExtension.hs | 303 ++++++++++++ compiler/hsSyn/HsImpExp.hs | 37 +- compiler/hsSyn/HsLit.hs | 131 ++++-- compiler/hsSyn/HsPat.hs | 168 +++---- compiler/hsSyn/HsPat.hs-boot | 6 +- compiler/hsSyn/HsSyn.hs | 7 +- compiler/hsSyn/HsTypes.hs | 385 ++++++++-------- compiler/hsSyn/HsUtils.hs | 296 ++++++------ compiler/hsSyn/PlaceHolder.hs | 50 -- compiler/main/GHC.hs | 8 +- compiler/main/HeaderInfo.hs | 7 +- compiler/main/Hooks.hs | 13 +- compiler/main/HscMain.hs | 16 +- compiler/main/HscStats.hs | 3 +- compiler/main/HscTypes.hs | 34 +- compiler/main/InteractiveEval.hs | 10 +- compiler/parser/Parser.y | 373 +++++++-------- compiler/parser/RdrHsSyn.hs | 243 +++++----- compiler/rename/RnBinds.hs | 147 +++--- compiler/rename/RnEnv.hs | 29 +- compiler/rename/RnExpr.hs | 221 ++++----- compiler/rename/RnExpr.hs-boot | 22 +- compiler/rename/RnFixity.hs | 2 +- compiler/rename/RnNames.hs | 85 ++-- compiler/rename/RnPat.hs | 63 +-- compiler/rename/RnSource.hs | 181 ++++---- compiler/rename/RnSplice.hs | 50 +- compiler/rename/RnSplice.hs-boot | 12 +- compiler/rename/RnTypes.hs | 209 ++++----- compiler/rename/RnUtils.hs | 2 +- compiler/typecheck/Inst.hs | 29 +- compiler/typecheck/TcAnnotations.hs | 17 +- compiler/typecheck/TcArrows.hs | 19 +- compiler/typecheck/TcBackpack.hs | 1 + compiler/typecheck/TcBinds.hs | 94 ++-- compiler/typecheck/TcClassDcl.hs | 41 +- compiler/typecheck/TcDefaults.hs | 8 +- compiler/typecheck/TcDeriv.hs | 39 +- compiler/typecheck/TcDerivUtils.hs | 8 +- compiler/typecheck/TcEnv.hs | 18 +- compiler/typecheck/TcEnv.hs-boot | 1 + compiler/typecheck/TcExpr.hs | 142 +++--- compiler/typecheck/TcExpr.hs-boot | 31 +- compiler/typecheck/TcForeign.hs | 19 +- compiler/typecheck/TcGenDeriv.hs | 144 +++--- compiler/typecheck/TcGenFunctor.hs | 99 ++-- compiler/typecheck/TcGenGenerics.hs | 32 +- compiler/typecheck/TcHsSyn.hs | 135 +++--- compiler/typecheck/TcHsType.hs | 92 ++-- compiler/typecheck/TcInstDcls.hs | 70 +-- compiler/typecheck/TcInstDcls.hs-boot | 4 +- compiler/typecheck/TcMatches.hs | 95 ++-- compiler/typecheck/TcMatches.hs-boot | 11 +- compiler/typecheck/TcPat.hs | 53 +-- compiler/typecheck/TcPatSyn.hs | 84 ++-- compiler/typecheck/TcPatSyn.hs-boot | 13 +- compiler/typecheck/TcRnDriver.hs | 59 +-- compiler/typecheck/TcRnExports.hs | 41 +- compiler/typecheck/TcRnTypes.hs | 72 +-- compiler/typecheck/TcRules.hs | 10 +- compiler/typecheck/TcSigs.hs | 34 +- compiler/typecheck/TcSplice.hs | 51 +- compiler/typecheck/TcSplice.hs-boot | 36 +- compiler/typecheck/TcTyClsDecls.hs | 111 ++--- compiler/typecheck/TcTyDecls.hs | 11 +- compiler/typecheck/TcTypeable.hs | 55 +-- compiler/typecheck/TcUnify.hs | 11 +- compiler/typecheck/TcUnify.hs-boot | 14 +- compiler/typecheck/TcValidity.hs | 2 +- ghc/GHCi/UI.hs | 6 +- ghc/GHCi/UI/Info.hs | 6 +- ghc/GHCi/UI/Monad.hs | 7 +- .../tests/ghc-api/annotations-literals/parsed.hs | 6 +- testsuite/tests/ghc-api/annotations/parseTree.hs | 2 +- .../tests/ghc-api/annotations/stringSource.hs | 6 +- testsuite/tests/ghc-api/annotations/t11430.hs | 4 +- testsuite/tests/quasiquotation/T7918.hs | 6 +- utils/ghctags/Main.hs | 5 +- utils/haddock | 2 +- 107 files changed, 3778 insertions(+), 3295 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 e511e8e1dc4d74bfab6b9fa7acd327082f459119 From git at git.haskell.org Sun May 28 13:23:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 28 May 2017 13:23:13 +0000 (UTC) Subject: [commit: ghc] wip/new-tree-one-param-2's head updated: Udate hsSyn AST to use Trees that Grow (e511e8e) Message-ID: <20170528132313.D053A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/new-tree-one-param-2' now includes: f011f58 rules: add per-library EXTRA_HC_OPTS 17055da A bit more tc-tracing c2eea08 Make isInsolubleOccursCheck more aggressive 8dc6d64 Re-engineer Given flatten-skolems 226860e Shrink a couple of hs-boot files ad14efd Some tidying up of type pretty-printing 19c4203 Typos in comments [ci skip] 7fce4cb Revert "Rewrite boot in Python" c823140 Add regression test for #13758 27f6f38 Add regression test for #12648 52fe138 user-guide: Add since annotation for -Wcpp-undef db1fd97 template-haskell: Properly escape StrTyLit doc 2944d27 Fix build after 'Shrink a couple of hs-boot files' 09d5c99 Fix test output after 'Some tidying up of type pretty-printing' 3b23f68 Remove HsContext from ppr_mono_ty, and remove ppParendHsType e511e8e Udate hsSyn AST to use Trees that Grow From git at git.haskell.org Mon May 29 17:09:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 17:09:12 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Nailed the Windows issue (b21a6e1) Message-ID: <20170529170912.11F123A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/b21a6e19854678838e103e4a76fe86abf36b8561/ghc >--------------------------------------------------------------- commit b21a6e19854678838e103e4a76fe86abf36b8561 Author: Ben Gamari Date: Mon May 29 12:48:34 2017 -0400 Nailed the Windows issue >--------------------------------------------------------------- b21a6e19854678838e103e4a76fe86abf36b8561 Jenkinsfile | 18 +++++++++++------- 1 file changed, 11 insertions(+), 7 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 0bd3c7b..20dbec0 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -24,6 +24,9 @@ parallel ( "aarch64" : { node(label: 'linux && aarch64') {buildGhc(runNoFib: false)} }, + "freebsd" : { + node(label: 'freebsd && aarch64') {buildGhc(runNoFib: false)} + }, // Requires cygpath plugin? // Make "windows 64" : { @@ -47,14 +50,10 @@ def buildGhc(params) { stage('Checkout') { checkout scm - if (msys) { - bat "git submodule update --init --recursive" - } else { - sh "git submodule update --init --recursive" - } + sh "git submodule update --init --recursive" } - stage('Build') { + stage('Configure') { def speed = 'NORMAL' if (params.nightly) { speed = 'SLOW' @@ -87,10 +86,15 @@ def buildGhc(params) { sh """ ./boot ./configure ${configure_opts} - make -j${env.THREADS} """ } + stage('Build') { + sh "make -j${env.THREADS}" + } +} + +def testGhc() { stage('Install testsuite dependencies') { if (params.nightly && !crossTarget) { def pkgs = ['mtl', 'parallel', 'parsec', 'primitive', 'QuickCheck', From git at git.haskell.org Mon May 29 17:09:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 17:09:14 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rework handling of Windows (73d6ae5) Message-ID: <20170529170914.C5B073A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/73d6ae523f318f8c69633461d4e3975be07ae060/ghc >--------------------------------------------------------------- commit 73d6ae523f318f8c69633461d4e3975be07ae060 Author: Ben Gamari Date: Mon May 29 13:08:49 2017 -0400 Rework handling of Windows >--------------------------------------------------------------- 73d6ae523f318f8c69633461d4e3975be07ae060 Jenkinsfile | 13 ++++++++++--- 1 file changed, 10 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 20dbec0..523ba7d 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -30,10 +30,18 @@ parallel ( // Requires cygpath plugin? // Make "windows 64" : { - node(label: 'windows && amd64') {buildGhc(msys: 64)} + environment { + PATH = 'C:\msys64\mingw64\bin:C:\msys64\home\ben\ghc-8.0.2-x86_64:$PATH' + } + node(label: 'windows && amd64') {buildGhc()} }, "windows 32" : { - node(label: 'windows && amd64') {buildGhc(msys: 32)} + node(label: 'windows && amd64') { + environment { + PATH = 'C:\msys64\mingw64\bin:C:\msys64\home\ben\ghc-8.0.2-x86_64:$PATH' + } + buildGhc() + } }, //"osx" : {node(label: 'darwin') {buildGhc(runNoFib: params.runNoFib)}} ) @@ -46,7 +54,6 @@ def buildGhc(params) { boolean runNoFib = params?.runNofib ?: false String crossTarget = params?.crossTarget boolean unreg = params?.unreg ?: false - String msys = params?.msys; stage('Checkout') { checkout scm From git at git.haskell.org Mon May 29 17:11:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 17:11:06 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rework handling of Windows (24ad3fb) Message-ID: <20170529171106.CED683A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/24ad3fb520a1ffb0c2aa945e1403a38f3322fee9/ghc >--------------------------------------------------------------- commit 24ad3fb520a1ffb0c2aa945e1403a38f3322fee9 Author: Ben Gamari Date: Mon May 29 13:08:49 2017 -0400 Rework handling of Windows >--------------------------------------------------------------- 24ad3fb520a1ffb0c2aa945e1403a38f3322fee9 Jenkinsfile | 13 ++++++++++--- 1 file changed, 10 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 20dbec0..3ad35f6 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -30,10 +30,18 @@ parallel ( // Requires cygpath plugin? // Make "windows 64" : { - node(label: 'windows && amd64') {buildGhc(msys: 64)} + environment { + PATH = 'C:\\msys64\\mingw64\\bin:C:\msys64\\home\\ben\\ghc-8.0.2-x86_64:$PATH' + } + node(label: 'windows && amd64') {buildGhc()} }, "windows 32" : { - node(label: 'windows && amd64') {buildGhc(msys: 32)} + node(label: 'windows && amd64') { + environment { + PATH = 'C:\\msys64\\mingw32\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-i386:$PATH' + } + buildGhc() + } }, //"osx" : {node(label: 'darwin') {buildGhc(runNoFib: params.runNoFib)}} ) @@ -46,7 +54,6 @@ def buildGhc(params) { boolean runNoFib = params?.runNofib ?: false String crossTarget = params?.crossTarget boolean unreg = params?.unreg ?: false - String msys = params?.msys; stage('Checkout') { checkout scm From git at git.haskell.org Mon May 29 17:11:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 17:11:54 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rework handling of Windows (bdfc0dd) Message-ID: <20170529171154.ACD033A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/bdfc0dd53e1ad595af6df87bebad402bbae4e396/ghc >--------------------------------------------------------------- commit bdfc0dd53e1ad595af6df87bebad402bbae4e396 Author: Ben Gamari Date: Mon May 29 13:08:49 2017 -0400 Rework handling of Windows >--------------------------------------------------------------- bdfc0dd53e1ad595af6df87bebad402bbae4e396 Jenkinsfile | 13 ++++++++++--- 1 file changed, 10 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 20dbec0..571cbb0 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -30,10 +30,18 @@ parallel ( // Requires cygpath plugin? // Make "windows 64" : { - node(label: 'windows && amd64') {buildGhc(msys: 64)} + environment { + PATH = 'C:\\msys64\\mingw64\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-x86_64:$PATH' + } + node(label: 'windows && amd64') {buildGhc()} }, "windows 32" : { - node(label: 'windows && amd64') {buildGhc(msys: 32)} + node(label: 'windows && amd64') { + environment { + PATH = 'C:\\msys64\\mingw32\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-i386:$PATH' + } + buildGhc() + } }, //"osx" : {node(label: 'darwin') {buildGhc(runNoFib: params.runNoFib)}} ) @@ -46,7 +54,6 @@ def buildGhc(params) { boolean runNoFib = params?.runNofib ?: false String crossTarget = params?.crossTarget boolean unreg = params?.unreg ?: false - String msys = params?.msys; stage('Checkout') { checkout scm From git at git.haskell.org Mon May 29 18:12:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 18:12:31 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix FreeBSD architecture (8b8b97d) Message-ID: <20170529181231.E79C23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/8b8b97d74a44dda2c60e800bf72d4ad92f1b2dba/ghc >--------------------------------------------------------------- commit 8b8b97d74a44dda2c60e800bf72d4ad92f1b2dba Author: Ben Gamari Date: Mon May 29 13:55:03 2017 -0400 Fix FreeBSD architecture >--------------------------------------------------------------- 8b8b97d74a44dda2c60e800bf72d4ad92f1b2dba Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 571cbb0..60d0b9d 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -25,7 +25,7 @@ parallel ( node(label: 'linux && aarch64') {buildGhc(runNoFib: false)} }, "freebsd" : { - node(label: 'freebsd && aarch64') {buildGhc(runNoFib: false)} + node(label: 'freebsd && amd64') {buildGhc(runNoFib: false)} }, // Requires cygpath plugin? // Make From git at git.haskell.org Mon May 29 18:12:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 18:12:34 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Build from source distribution (ced26f5) Message-ID: <20170529181234.ABB793A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ced26f56fe8bf35ed475a31300e8e20776a43672/ghc >--------------------------------------------------------------- commit ced26f56fe8bf35ed475a31300e8e20776a43672 Author: Ben Gamari Date: Mon May 29 13:55:58 2017 -0400 Build from source distribution >--------------------------------------------------------------- ced26f56fe8bf35ed475a31300e8e20776a43672 Jenkinsfile | 14 ++++++++++++-- 1 file changed, 12 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 60d0b9d..3e79e22 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,6 +11,15 @@ properties( ]) ]) + +stage("Build source distribution") { + checkout csm + sh "git submodule update --init --recursive" + sh "make sdist" + sh "mv ghc-*.tar.xz" "ghc-src.tar.xz" + stash(name: 'source-dist', includes: 'ghc-src.tar.xz') +} + parallel ( "linux x86-64" : { node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib)} @@ -56,8 +65,9 @@ def buildGhc(params) { boolean unreg = params?.unreg ?: false stage('Checkout') { - checkout scm - sh "git submodule update --init --recursive" + unstash(name: "source-dist") + sh 'tar -xf ghc-src.tar.xz' + dir 'ghc-*' } stage('Configure') { From git at git.haskell.org Mon May 29 18:13:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 18:13:43 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Build from source distribution (2b88a0f) Message-ID: <20170529181343.AAC473A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2b88a0f518a18e9401dee7ee05cf63d6b43d5adb/ghc >--------------------------------------------------------------- commit 2b88a0f518a18e9401dee7ee05cf63d6b43d5adb Author: Ben Gamari Date: Mon May 29 13:55:58 2017 -0400 Build from source distribution >--------------------------------------------------------------- 2b88a0f518a18e9401dee7ee05cf63d6b43d5adb Jenkinsfile | 16 ++++++++++++++-- 1 file changed, 14 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 60d0b9d..ba107d9 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,6 +11,17 @@ properties( ]) ]) + +stage("Build source distribution") { + node() { + checkout csm + sh "git submodule update --init --recursive" + sh "make sdist" + sh "mv ghc-*.tar.xz" "ghc-src.tar.xz" + stash(name: 'source-dist', includes: 'ghc-src.tar.xz') + } +} + parallel ( "linux x86-64" : { node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib)} @@ -56,8 +67,9 @@ def buildGhc(params) { boolean unreg = params?.unreg ?: false stage('Checkout') { - checkout scm - sh "git submodule update --init --recursive" + unstash(name: "source-dist") + sh 'tar -xf ghc-src.tar.xz' + dir 'ghc-*' } stage('Configure') { From git at git.haskell.org Mon May 29 18:14:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 18:14:26 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Build from source distribution (cac622a) Message-ID: <20170529181426.6319E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/cac622acdbaa586cebace6ff2acc9e4d4bc7f32f/ghc >--------------------------------------------------------------- commit cac622acdbaa586cebace6ff2acc9e4d4bc7f32f Author: Ben Gamari Date: Mon May 29 13:55:58 2017 -0400 Build from source distribution >--------------------------------------------------------------- cac622acdbaa586cebace6ff2acc9e4d4bc7f32f Jenkinsfile | 16 ++++++++++++++-- 1 file changed, 14 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 60d0b9d..d822d00 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,6 +11,17 @@ properties( ]) ]) + +stage("Build source distribution") { + node() { + checkout scm + sh "git submodule update --init --recursive" + sh "make sdist" + sh "mv ghc-*.tar.xz" "ghc-src.tar.xz" + stash(name: 'source-dist', includes: 'ghc-src.tar.xz') + } +} + parallel ( "linux x86-64" : { node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib)} @@ -56,8 +67,9 @@ def buildGhc(params) { boolean unreg = params?.unreg ?: false stage('Checkout') { - checkout scm - sh "git submodule update --init --recursive" + unstash(name: "source-dist") + sh 'tar -xf ghc-src.tar.xz' + dir 'ghc-*' } stage('Configure') { From git at git.haskell.org Mon May 29 18:19:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 18:19:46 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Build from source distribution (7faf062) Message-ID: <20170529181946.6B00C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7faf0622e8df5553eddf6cb32bf4c31225653e88/ghc >--------------------------------------------------------------- commit 7faf0622e8df5553eddf6cb32bf4c31225653e88 Author: Ben Gamari Date: Mon May 29 13:55:58 2017 -0400 Build from source distribution >--------------------------------------------------------------- 7faf0622e8df5553eddf6cb32bf4c31225653e88 Jenkinsfile | 16 ++++++++++++++-- 1 file changed, 14 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 60d0b9d..56e590f 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,6 +11,17 @@ properties( ]) ]) + +stage("Build source distribution") { + node(label: 'linux') { + checkout scm + sh "git submodule update --init --recursive" + sh "make sdist" + sh "mv ghc-*.tar.xz" "ghc-src.tar.xz" + stash(name: 'source-dist', includes: 'ghc-src.tar.xz') + } +} + parallel ( "linux x86-64" : { node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib)} @@ -56,8 +67,9 @@ def buildGhc(params) { boolean unreg = params?.unreg ?: false stage('Checkout') { - checkout scm - sh "git submodule update --init --recursive" + unstash(name: "source-dist") + sh 'tar -xf ghc-src.tar.xz' + dir 'ghc-*' } stage('Configure') { From git at git.haskell.org Mon May 29 18:20:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 18:20:53 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Build from source distribution (daf2cb7) Message-ID: <20170529182053.349AC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/daf2cb7eed8e77f349666302a7116312875150ff/ghc >--------------------------------------------------------------- commit daf2cb7eed8e77f349666302a7116312875150ff Author: Ben Gamari Date: Mon May 29 13:55:58 2017 -0400 Build from source distribution >--------------------------------------------------------------- daf2cb7eed8e77f349666302a7116312875150ff Jenkinsfile | 20 ++++++++++++++++++-- 1 file changed, 18 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 60d0b9d..9b66653 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,6 +11,21 @@ properties( ]) ]) + +stage("Build source distribution") { + node(label: 'linux') { + checkout scm + sh "git submodule update --init --recursive" + sh """ + ./boot + ./configure + make sdist" + """ + sh "mv ghc-*.tar.xz" "ghc-src.tar.xz" + stash(name: 'source-dist', includes: 'ghc-src.tar.xz') + } +} + parallel ( "linux x86-64" : { node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib)} @@ -56,8 +71,9 @@ def buildGhc(params) { boolean unreg = params?.unreg ?: false stage('Checkout') { - checkout scm - sh "git submodule update --init --recursive" + unstash(name: "source-dist") + sh 'tar -xf ghc-src.tar.xz' + dir 'ghc-*' } stage('Configure') { From git at git.haskell.org Mon May 29 18:21:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 18:21:47 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Build from source distribution (505b638) Message-ID: <20170529182147.BCD493A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/505b6382c0d795605dae5a0aee0e6f79082bf539/ghc >--------------------------------------------------------------- commit 505b6382c0d795605dae5a0aee0e6f79082bf539 Author: Ben Gamari Date: Mon May 29 13:55:58 2017 -0400 Build from source distribution >--------------------------------------------------------------- 505b6382c0d795605dae5a0aee0e6f79082bf539 Jenkinsfile | 20 ++++++++++++++++++-- 1 file changed, 18 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 60d0b9d..a71d09d 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,6 +11,21 @@ properties( ]) ]) + +stage("Build source distribution") { + node(label: 'linux') { + checkout scm + sh "git submodule update --init --recursive" + sh """ + ./boot + ./configure + make sdist + """ + sh "mv ghc-*.tar.xz" "ghc-src.tar.xz" + stash(name: 'source-dist', includes: 'ghc-src.tar.xz') + } +} + parallel ( "linux x86-64" : { node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib)} @@ -56,8 +71,9 @@ def buildGhc(params) { boolean unreg = params?.unreg ?: false stage('Checkout') { - checkout scm - sh "git submodule update --init --recursive" + unstash(name: "source-dist") + sh 'tar -xf ghc-src.tar.xz' + dir 'ghc-*' } stage('Configure') { From git at git.haskell.org Mon May 29 18:22:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 18:22:51 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Build from source distribution (9ad430c) Message-ID: <20170529182251.580D53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9ad430ced2c486722665c7dd4ef974116dba79e8/ghc >--------------------------------------------------------------- commit 9ad430ced2c486722665c7dd4ef974116dba79e8 Author: Ben Gamari Date: Mon May 29 13:55:58 2017 -0400 Build from source distribution >--------------------------------------------------------------- 9ad430ced2c486722665c7dd4ef974116dba79e8 Jenkinsfile | 18 ++++++++++++++++-- 1 file changed, 16 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 60d0b9d..2fc6ecd 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,6 +11,19 @@ properties( ]) ]) + +stage("Build source distribution") { + checkout scm + sh "git submodule update --init --recursive" + sh """ + ./boot + ./configure + make sdist + """ + sh "mv ghc-*.tar.xz" "ghc-src.tar.xz" + stash(name: 'source-dist', includes: 'ghc-src.tar.xz') +} + parallel ( "linux x86-64" : { node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib)} @@ -56,8 +69,9 @@ def buildGhc(params) { boolean unreg = params?.unreg ?: false stage('Checkout') { - checkout scm - sh "git submodule update --init --recursive" + unstash(name: "source-dist") + sh 'tar -xf ghc-src.tar.xz' + dir 'ghc-*' } stage('Configure') { From git at git.haskell.org Mon May 29 18:24:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 18:24:12 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Build from source distribution (d1306ae) Message-ID: <20170529182412.071AB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d1306ae74405c8ef621e92b34ec47774f62a8541/ghc >--------------------------------------------------------------- commit d1306ae74405c8ef621e92b34ec47774f62a8541 Author: Ben Gamari Date: Mon May 29 13:55:58 2017 -0400 Build from source distribution >--------------------------------------------------------------- d1306ae74405c8ef621e92b34ec47774f62a8541 Jenkinsfile | 20 ++++++++++++++++++-- 1 file changed, 18 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 60d0b9d..a71d09d 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -11,6 +11,21 @@ properties( ]) ]) + +stage("Build source distribution") { + node(label: 'linux') { + checkout scm + sh "git submodule update --init --recursive" + sh """ + ./boot + ./configure + make sdist + """ + sh "mv ghc-*.tar.xz" "ghc-src.tar.xz" + stash(name: 'source-dist', includes: 'ghc-src.tar.xz') + } +} + parallel ( "linux x86-64" : { node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib)} @@ -56,8 +71,9 @@ def buildGhc(params) { boolean unreg = params?.unreg ?: false stage('Checkout') { - checkout scm - sh "git submodule update --init --recursive" + unstash(name: "source-dist") + sh 'tar -xf ghc-src.tar.xz' + dir 'ghc-*' } stage('Configure') { From git at git.haskell.org Mon May 29 19:49:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 19:49:54 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Parametrize on make command (e292a5f) Message-ID: <20170529194954.416B23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/e292a5ffb7e93246284a5f8c10bbbfe785d69b34/ghc >--------------------------------------------------------------- commit e292a5ffb7e93246284a5f8c10bbbfe785d69b34 Author: Ben Gamari Date: Mon May 29 15:44:39 2017 -0400 Parametrize on make command >--------------------------------------------------------------- e292a5ffb7e93246284a5f8c10bbbfe785d69b34 Jenkinsfile | 19 +++++++++++-------- 1 file changed, 11 insertions(+), 8 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 60d0b9d..8ec33cd 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -25,7 +25,7 @@ parallel ( node(label: 'linux && aarch64') {buildGhc(runNoFib: false)} }, "freebsd" : { - node(label: 'freebsd && amd64') {buildGhc(runNoFib: false)} + node(label: 'freebsd && amd64') {buildGhc(runNoFib: false, makeCmd: 'gmake')} }, // Requires cygpath plugin? // Make @@ -54,6 +54,7 @@ def buildGhc(params) { boolean runNoFib = params?.runNofib ?: false String crossTarget = params?.crossTarget boolean unreg = params?.unreg ?: false + String makeCmd = params?.makeCmd ?: 'make' stage('Checkout') { checkout scm @@ -97,11 +98,13 @@ def buildGhc(params) { } stage('Build') { - sh "make -j${env.THREADS}" + sh "${makeCmd} -j${env.THREADS}" } } -def testGhc() { +def testGhc(params) { + String makeCmd = params?.makeCmd ?: 'make' + stage('Install testsuite dependencies') { if (params.nightly && !crossTarget) { def pkgs = ['mtl', 'parallel', 'parsec', 'primitive', 'QuickCheck', @@ -117,7 +120,7 @@ def testGhc() { if (params.nightly) { target = 'slowtest' } - sh "make THREADS=${env.THREADS} ${target}" + sh "${makeCmd} THREADS=${env.THREADS} ${target}" } } @@ -126,9 +129,9 @@ def testGhc() { installPkgs(['regex-compat']) sh """ cd nofib - make clean - make boot - make >../nofib.log 2>&1 + ${makeCmd} clean + ${makeCmd} boot + ${makeCmd} >../nofib.log 2>&1 """ archive 'nofib.log' } @@ -136,8 +139,8 @@ def testGhc() { stage('Prepare bindist') { if (params.buildBindist) { - sh "make binary-dist" archive 'ghc-*.tar.xz' + sh "${makeCmd} binary-dist" } } } From git at git.haskell.org Mon May 29 19:49:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 19:49:56 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Use archiveArtifacts instead of archive (2f5a7d4) Message-ID: <20170529194956.EF52D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2f5a7d494fb4e3c648e96f2e0da1f6fab95ced08/ghc >--------------------------------------------------------------- commit 2f5a7d494fb4e3c648e96f2e0da1f6fab95ced08 Author: Ben Gamari Date: Mon May 29 15:44:56 2017 -0400 Use archiveArtifacts instead of archive >--------------------------------------------------------------- 2f5a7d494fb4e3c648e96f2e0da1f6fab95ced08 Jenkinsfile | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 8ec33cd..8a621a8 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -133,14 +133,14 @@ def testGhc(params) { ${makeCmd} boot ${makeCmd} >../nofib.log 2>&1 """ - archive 'nofib.log' + archiveArtifacts 'nofib.log' } } stage('Prepare bindist') { if (params.buildBindist) { - archive 'ghc-*.tar.xz' sh "${makeCmd} binary-dist" + archiveArtifacts 'ghc-*.tar.xz' } } } From git at git.haskell.org Mon May 29 19:49:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 19:49:59 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (961ecc3) Message-ID: <20170529194959.A7C443A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/961ecc3d68620da7b58abe30fcebf95b31f1e1e5/ghc >--------------------------------------------------------------- commit 961ecc3d68620da7b58abe30fcebf95b31f1e1e5 Author: Ben Gamari Date: Mon May 29 15:49:33 2017 -0400 Debug >--------------------------------------------------------------- 961ecc3d68620da7b58abe30fcebf95b31f1e1e5 Jenkinsfile | 3 --- 1 file changed, 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 8a621a8..f32df3f 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -30,9 +30,6 @@ parallel ( // Requires cygpath plugin? // Make "windows 64" : { - environment { - PATH = 'C:\\msys64\\mingw64\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-x86_64:$PATH' - } node(label: 'windows && amd64') {buildGhc()} }, "windows 32" : { From git at git.haskell.org Mon May 29 20:14:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 20:14:26 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Don't run nofib on Windows (67c04c0) Message-ID: <20170529201426.249573A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/67c04c08853044943d67a9bb553ba7b227f50840/ghc >--------------------------------------------------------------- commit 67c04c08853044943d67a9bb553ba7b227f50840 Author: Ben Gamari Date: Mon May 29 16:14:11 2017 -0400 Don't run nofib on Windows >--------------------------------------------------------------- 67c04c08853044943d67a9bb553ba7b227f50840 Jenkinsfile | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index f32df3f..84c175e 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -30,14 +30,14 @@ parallel ( // Requires cygpath plugin? // Make "windows 64" : { - node(label: 'windows && amd64') {buildGhc()} + node(label: 'windows && amd64') {buildGhc(runNoFib: false)} }, "windows 32" : { node(label: 'windows && amd64') { environment { PATH = 'C:\\msys64\\mingw32\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-i386:$PATH' } - buildGhc() + buildGhc(runNoFib: false) } }, //"osx" : {node(label: 'darwin') {buildGhc(runNoFib: params.runNoFib)}} From git at git.haskell.org Mon May 29 20:31:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 20:31:40 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix Windows PATHs (ec4c58a) Message-ID: <20170529203140.301F43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ec4c58a1cca29cf56062a65d61ada8475cbc9803/ghc >--------------------------------------------------------------- commit ec4c58a1cca29cf56062a65d61ada8475cbc9803 Author: Ben Gamari Date: Mon May 29 16:31:28 2017 -0400 Fix Windows PATHs >--------------------------------------------------------------- ec4c58a1cca29cf56062a65d61ada8475cbc9803 Jenkinsfile | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 84c175e..10d2280 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -30,12 +30,17 @@ parallel ( // Requires cygpath plugin? // Make "windows 64" : { + environment { + MSYSTEM=MINGW32 + PATH = 'C:\\msys64\\mingw32\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-i386\\bin:$PATH' + } node(label: 'windows && amd64') {buildGhc(runNoFib: false)} }, "windows 32" : { node(label: 'windows && amd64') { environment { - PATH = 'C:\\msys64\\mingw32\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-i386:$PATH' + MSYSTEM=MINGW64 + PATH = 'C:\\msys64\\mingw32\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-i386\\bin:$PATH' } buildGhc(runNoFib: false) } From git at git.haskell.org Mon May 29 20:34:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 20:34:43 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Disable large address space on FreeBSD (a4faeed) Message-ID: <20170529203443.450A33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a4faeed6e3faa8026234fc4b4d7ee9d2fa2dec69/ghc >--------------------------------------------------------------- commit a4faeed6e3faa8026234fc4b4d7ee9d2fa2dec69 Author: Ben Gamari Date: Mon May 29 16:34:26 2017 -0400 Disable large address space on FreeBSD >--------------------------------------------------------------- a4faeed6e3faa8026234fc4b4d7ee9d2fa2dec69 Jenkinsfile | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 10d2280..eac4b79 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -25,7 +25,9 @@ parallel ( node(label: 'linux && aarch64') {buildGhc(runNoFib: false)} }, "freebsd" : { - node(label: 'freebsd && amd64') {buildGhc(runNoFib: false, makeCmd: 'gmake')} + node(label: 'freebsd && amd64') { + buildGhc(runNoFib: false, makeCmd: 'gmake', disableLargeAddrSpace: true) + } }, // Requires cygpath plugin? // Make @@ -56,6 +58,7 @@ def buildGhc(params) { boolean runNoFib = params?.runNofib ?: false String crossTarget = params?.crossTarget boolean unreg = params?.unreg ?: false + boolean disableLargeAddrSpace = params?.disableLargeAddrSpace ?: false String makeCmd = params?.makeCmd ?: 'make' stage('Checkout') { @@ -90,6 +93,9 @@ def buildGhc(params) { if (crossTarget) { configure_opts += "--target=${crossTarget}" } + if (disableLargeAddrSpace) { + configure_opts += "--disable-large-address-space" + } if (unreg) { configure_opts += "--enable-unregisterised" } From git at git.haskell.org Mon May 29 20:42:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 20:42:52 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Try again (80eb484) Message-ID: <20170529204252.E40123A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/80eb484ee85c0de5506ce9ef6d8639e00497d17f/ghc >--------------------------------------------------------------- commit 80eb484ee85c0de5506ce9ef6d8639e00497d17f Author: Ben Gamari Date: Mon May 29 16:42:42 2017 -0400 Try again >--------------------------------------------------------------- 80eb484ee85c0de5506ce9ef6d8639e00497d17f Jenkinsfile | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index eac4b79..69960f2 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -32,11 +32,14 @@ parallel ( // Requires cygpath plugin? // Make "windows 64" : { - environment { - MSYSTEM=MINGW32 - PATH = 'C:\\msys64\\mingw32\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-i386\\bin:$PATH' - } - node(label: 'windows && amd64') {buildGhc(runNoFib: false)} + node(label: 'windows && amd64') { + sh """ + export MSYSTEM=MINGW32 + # PATH = 'C:\\msys64\\mingw32\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-i386\\bin:$PATH' + source /etc/profile + """ + buildGhc(runNoFib: false) + } }, "windows 32" : { node(label: 'windows && amd64') { From git at git.haskell.org Mon May 29 20:57:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 20:57:48 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Hmm (7937e28) Message-ID: <20170529205748.EA9ED3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7937e2814a805d3604027b190bf25d770f14bd2b/ghc >--------------------------------------------------------------- commit 7937e2814a805d3604027b190bf25d770f14bd2b Author: Ben Gamari Date: Mon May 29 16:45:16 2017 -0400 Hmm >--------------------------------------------------------------- 7937e2814a805d3604027b190bf25d770f14bd2b Jenkinsfile | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 69960f2..66c8488 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -35,8 +35,10 @@ parallel ( node(label: 'windows && amd64') { sh """ export MSYSTEM=MINGW32 - # PATH = 'C:\\msys64\\mingw32\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-i386\\bin:$PATH' + # Profile tries to read PRINTER and fails due to lack of a newline, hence disabling e + set +e source /etc/profile + set -e """ buildGhc(runNoFib: false) } From git at git.haskell.org Mon May 29 22:33:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 22:33:46 +0000 (UTC) Subject: [commit: ghc] master: Modern type signature style in UniqSet (b5c73a9) Message-ID: <20170529223346.E1FA63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b5c73a9e1fb00f21831f3576f090ac7be3864c89/ghc >--------------------------------------------------------------- commit b5c73a9e1fb00f21831f3576f090ac7be3864c89 Author: Bartosz Nitka Date: Mon May 29 15:30:06 2017 -0700 Modern type signature style in UniqSet >--------------------------------------------------------------- b5c73a9e1fb00f21831f3576f090ac7be3864c89 compiler/basicTypes/VarSet.hs | 6 +- compiler/utils/UniqSet.hs | 147 ++++++++++++++++++++---------------------- 2 files changed, 74 insertions(+), 79 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 b5c73a9e1fb00f21831f3576f090ac7be3864c89 From git at git.haskell.org Mon May 29 23:34:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 May 2017 23:34:26 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Disable non-Windows builds (3558003) Message-ID: <20170529233426.5C5883A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/3558003d8b7855c7451744c6f836138c96f59eeb/ghc >--------------------------------------------------------------- commit 3558003d8b7855c7451744c6f836138c96f59eeb Author: Ben Gamari Date: Mon May 29 19:34:11 2017 -0400 Disable non-Windows builds >--------------------------------------------------------------- 3558003d8b7855c7451744c6f836138c96f59eeb Jenkinsfile | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/Jenkinsfile b/Jenkinsfile index 66c8488..e320c49 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -12,6 +12,7 @@ properties( ]) parallel ( + /* "linux x86-64" : { node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib)} }, @@ -29,6 +30,7 @@ parallel ( buildGhc(runNoFib: false, makeCmd: 'gmake', disableLargeAddrSpace: true) } }, + */ // Requires cygpath plugin? // Make "windows 64" : { @@ -43,6 +45,7 @@ parallel ( buildGhc(runNoFib: false) } }, + /* "windows 32" : { node(label: 'windows && amd64') { environment { @@ -52,6 +55,7 @@ parallel ( buildGhc(runNoFib: false) } }, + */ //"osx" : {node(label: 'darwin') {buildGhc(runNoFib: params.runNoFib)}} ) From git at git.haskell.org Tue May 30 02:34:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 02:34:04 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Hopefully fix Windows (614e219) Message-ID: <20170530023404.05E993A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/614e219099fa941590314091ea8e39cb370f7bad/ghc >--------------------------------------------------------------- commit 614e219099fa941590314091ea8e39cb370f7bad Author: Ben Gamari Date: Mon May 29 22:33:46 2017 -0400 Hopefully fix Windows >--------------------------------------------------------------- 614e219099fa941590314091ea8e39cb370f7bad Jenkinsfile | 38 ++++++++++++++++++++++++++------------ 1 file changed, 26 insertions(+), 12 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index e320c49..b23c422 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -35,23 +35,12 @@ parallel ( // Make "windows 64" : { node(label: 'windows && amd64') { - sh """ - export MSYSTEM=MINGW32 - # Profile tries to read PRINTER and fails due to lack of a newline, hence disabling e - set +e - source /etc/profile - set -e - """ - buildGhc(runNoFib: false) + withMingw('MINGW64') buildGhc(runNoFib: false) } }, /* "windows 32" : { node(label: 'windows && amd64') { - environment { - MSYSTEM=MINGW64 - PATH = 'C:\\msys64\\mingw32\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-i386\\bin:$PATH' - } buildGhc(runNoFib: false) } }, @@ -59,6 +48,31 @@ parallel ( //"osx" : {node(label: 'darwin') {buildGhc(runNoFib: params.runNoFib)}} ) +def withMingw(String msystem, Closure f) { + def msysRoot = 'C:\\msys64' + if (msystem == 'MINGW32') { + prefix = '${msysRoot}\\mingw32' + carch = 'i686' + } else if (msystem == 'MINGW64') { + prefix = '${msysRoot}\\mingw64' + carch = 'x86_64' + } else { + fail + } + chost = '${carch}-w64-mingw32' + + withEnv(['MSYSTEM=${msystem}', + 'PATH=C:\\msys64\\mingw32\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-i386\\bin:$PATH', + 'MSYSTEM_PREFIX=${prefix}', + 'MSYSTEM_CARCH=${carch}', + 'MSYSTEM_CHOST=${chost}', + 'MINGW_CHOST=${chost}', + 'MINGW_PREFIX=${prefix}', + 'MINGW_PACKAGE_PREFIX=mingw-w64-${MSYSTEM_CARCH}', + 'CONFIG_SIET=${prefix}/etc/config.site' + ], f) +} + def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } From git at git.haskell.org Tue May 30 02:36:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 02:36:03 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Hopefully fix Windows (aff3540) Message-ID: <20170530023603.5CCF73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/aff3540120e9b51bdd904c23a34966c1b69182af/ghc >--------------------------------------------------------------- commit aff3540120e9b51bdd904c23a34966c1b69182af Author: Ben Gamari Date: Mon May 29 22:33:46 2017 -0400 Hopefully fix Windows >--------------------------------------------------------------- aff3540120e9b51bdd904c23a34966c1b69182af Jenkinsfile | 38 ++++++++++++++++++++++++++------------ 1 file changed, 26 insertions(+), 12 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index e320c49..768f942 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -35,23 +35,12 @@ parallel ( // Make "windows 64" : { node(label: 'windows && amd64') { - sh """ - export MSYSTEM=MINGW32 - # Profile tries to read PRINTER and fails due to lack of a newline, hence disabling e - set +e - source /etc/profile - set -e - """ - buildGhc(runNoFib: false) + withMingw('MINGW64') { buildGhc(runNoFib: false) } } }, /* "windows 32" : { node(label: 'windows && amd64') { - environment { - MSYSTEM=MINGW64 - PATH = 'C:\\msys64\\mingw32\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-i386\\bin:$PATH' - } buildGhc(runNoFib: false) } }, @@ -59,6 +48,31 @@ parallel ( //"osx" : {node(label: 'darwin') {buildGhc(runNoFib: params.runNoFib)}} ) +def withMingw(String msystem, Closure f) { + def msysRoot = 'C:\\msys64' + if (msystem == 'MINGW32') { + prefix = '${msysRoot}\\mingw32' + carch = 'i686' + } else if (msystem == 'MINGW64') { + prefix = '${msysRoot}\\mingw64' + carch = 'x86_64' + } else { + fail + } + chost = '${carch}-w64-mingw32' + + withEnv(['MSYSTEM=${msystem}', + 'PATH=C:\\msys64\\mingw32\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-i386\\bin:$PATH', + 'MSYSTEM_PREFIX=${prefix}', + 'MSYSTEM_CARCH=${carch}', + 'MSYSTEM_CHOST=${chost}', + 'MINGW_CHOST=${chost}', + 'MINGW_PREFIX=${prefix}', + 'MINGW_PACKAGE_PREFIX=mingw-w64-${MSYSTEM_CARCH}', + 'CONFIG_SIET=${prefix}/etc/config.site' + ], f) +} + def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } From git at git.haskell.org Tue May 30 02:39:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 02:39:12 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Hopefully fix Windows (ed2e09c) Message-ID: <20170530023912.CAED13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ed2e09c28b20a720b5fa81686901739ec25ecd8f/ghc >--------------------------------------------------------------- commit ed2e09c28b20a720b5fa81686901739ec25ecd8f Author: Ben Gamari Date: Mon May 29 22:33:46 2017 -0400 Hopefully fix Windows >--------------------------------------------------------------- ed2e09c28b20a720b5fa81686901739ec25ecd8f Jenkinsfile | 38 ++++++++++++++++++++++++++------------ 1 file changed, 26 insertions(+), 12 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index e320c49..1d2af80 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -35,23 +35,12 @@ parallel ( // Make "windows 64" : { node(label: 'windows && amd64') { - sh """ - export MSYSTEM=MINGW32 - # Profile tries to read PRINTER and fails due to lack of a newline, hence disabling e - set +e - source /etc/profile - set -e - """ - buildGhc(runNoFib: false) + withMingw('MINGW64') { buildGhc(runNoFib: false) } } }, /* "windows 32" : { node(label: 'windows && amd64') { - environment { - MSYSTEM=MINGW64 - PATH = 'C:\\msys64\\mingw32\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-i386\\bin:$PATH' - } buildGhc(runNoFib: false) } }, @@ -59,6 +48,31 @@ parallel ( //"osx" : {node(label: 'darwin') {buildGhc(runNoFib: params.runNoFib)}} ) +def withMingw(String msystem, Closure f) { + def msysRoot = 'C:\\msys64' + if (msystem == 'MINGW32') { + prefix = '${msysRoot}\\mingw32' + carch = 'i686' + } else if (msystem == 'MINGW64') { + prefix = '${msysRoot}\\mingw64' + carch = 'x86_64' + } else { + fail + } + chost = '${carch}-w64-mingw32' + + withEnv(['MSYSTEM=${msystem}', + 'PATH+mingw=C:\\msys64\\mingw32\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-i386\\bin', + 'MSYSTEM_PREFIX=${prefix}', + 'MSYSTEM_CARCH=${carch}', + 'MSYSTEM_CHOST=${chost}', + 'MINGW_CHOST=${chost}', + 'MINGW_PREFIX=${prefix}', + 'MINGW_PACKAGE_PREFIX=mingw-w64-${MSYSTEM_CARCH}', + 'CONFIG_SIET=${prefix}/etc/config.site' + ], f) +} + def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } From git at git.haskell.org Tue May 30 02:40:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 02:40:48 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Hopefully fix Windows (6e4c40e) Message-ID: <20170530024048.C386A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/6e4c40e66c37ab8dcd7daacd8756e329e764f735/ghc >--------------------------------------------------------------- commit 6e4c40e66c37ab8dcd7daacd8756e329e764f735 Author: Ben Gamari Date: Mon May 29 22:33:46 2017 -0400 Hopefully fix Windows >--------------------------------------------------------------- 6e4c40e66c37ab8dcd7daacd8756e329e764f735 Jenkinsfile | 38 ++++++++++++++++++++++++++------------ 1 file changed, 26 insertions(+), 12 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index e320c49..9c86c4a 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -35,23 +35,12 @@ parallel ( // Make "windows 64" : { node(label: 'windows && amd64') { - sh """ - export MSYSTEM=MINGW32 - # Profile tries to read PRINTER and fails due to lack of a newline, hence disabling e - set +e - source /etc/profile - set -e - """ - buildGhc(runNoFib: false) + withMingw('MINGW64') { buildGhc(runNoFib: false) } } }, /* "windows 32" : { node(label: 'windows && amd64') { - environment { - MSYSTEM=MINGW64 - PATH = 'C:\\msys64\\mingw32\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-i386\\bin:$PATH' - } buildGhc(runNoFib: false) } }, @@ -59,6 +48,31 @@ parallel ( //"osx" : {node(label: 'darwin') {buildGhc(runNoFib: params.runNoFib)}} ) +def withMingw(String msystem, Closure f) { + def msysRoot = 'C:\\msys64' + if (msystem == 'MINGW32') { + prefix = '${msysRoot}\\mingw32' + carch = 'i686' + } else if (msystem == 'MINGW64') { + prefix = '${msysRoot}\\mingw64' + carch = 'x86_64' + } else { + fail + } + chost = '${carch}-w64-mingw32' + + withEnv(["MSYSTEM=${msystem}", + "PATH+mingw=C:\\msys64\\mingw32\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-i386\\bin", + "MSYSTEM_PREFIX=${prefix}", + "MSYSTEM_CARCH=${carch}", + "MSYSTEM_CHOST=${chost}", + "MINGW_CHOST=${chost}", + "MINGW_PREFIX=${prefix}", + "MINGW_PACKAGE_PREFIX=mingw-w64-${MSYSTEM_CARCH}", + "CONFIG_SITE=${prefix}/etc/config.site" + ], f) +} + def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } From git at git.haskell.org Tue May 30 02:45:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 02:45:39 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Reenable everything else (79b150d) Message-ID: <20170530024539.9D7D73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/79b150d1970c706883e46033d68d1de6c3e47e54/ghc >--------------------------------------------------------------- commit 79b150d1970c706883e46033d68d1de6c3e47e54 Author: Ben Gamari Date: Mon May 29 22:45:19 2017 -0400 Reenable everything else >--------------------------------------------------------------- 79b150d1970c706883e46033d68d1de6c3e47e54 Jenkinsfile | 8 ++------ 1 file changed, 2 insertions(+), 6 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 9c86c4a..90cf036 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -12,7 +12,6 @@ properties( ]) parallel ( - /* "linux x86-64" : { node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib)} }, @@ -30,25 +29,22 @@ parallel ( buildGhc(runNoFib: false, makeCmd: 'gmake', disableLargeAddrSpace: true) } }, - */ // Requires cygpath plugin? - // Make "windows 64" : { node(label: 'windows && amd64') { withMingw('MINGW64') { buildGhc(runNoFib: false) } } }, - /* "windows 32" : { node(label: 'windows && amd64') { - buildGhc(runNoFib: false) + withMingw('MINGW64') { buildGhc(runNoFib: false) } } }, - */ //"osx" : {node(label: 'darwin') {buildGhc(runNoFib: params.runNoFib)}} ) def withMingw(String msystem, Closure f) { + // Derived from msys2's /etc/msystem def msysRoot = 'C:\\msys64' if (msystem == 'MINGW32') { prefix = '${msysRoot}\\mingw32' From git at git.haskell.org Tue May 30 02:56:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 02:56:10 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix configure arguments (00e6918) Message-ID: <20170530025610.D77283A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/00e69186276a3d90f7b9727c46de6c5c851d3db9/ghc >--------------------------------------------------------------- commit 00e69186276a3d90f7b9727c46de6c5c851d3db9 Author: Ben Gamari Date: Mon May 29 22:55:51 2017 -0400 Fix configure arguments >--------------------------------------------------------------- 00e69186276a3d90f7b9727c46de6c5c851d3db9 Jenkinsfile | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 90cf036..b2bd47a 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -108,19 +108,19 @@ def buildGhc(params) { } writeFile(file: 'mk/build.mk', text: build_mk) - def configure_opts = '--enable-tarballs-autodownload' + def configure_opts = ['--enable-tarballs-autodownload'] if (crossTarget) { - configure_opts += "--target=${crossTarget}" + configure_opts += '--target=${crossTarget}' } if (disableLargeAddrSpace) { - configure_opts += "--disable-large-address-space" + configure_opts += '--disable-large-address-space' } if (unreg) { - configure_opts += "--enable-unregisterised" + configure_opts += '--enable-unregisterised' } sh """ ./boot - ./configure ${configure_opts} + ./configure ${configure_opts.join(' ')} """ } From git at git.haskell.org Tue May 30 04:29:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 04:29:41 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Clean (0ca4ba5) Message-ID: <20170530042941.9A1E03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0ca4ba59e2e3ed57f34cf239fc41b2471a8b8040/ghc >--------------------------------------------------------------- commit 0ca4ba59e2e3ed57f34cf239fc41b2471a8b8040 Author: Ben Gamari Date: Tue May 30 00:29:29 2017 -0400 Clean >--------------------------------------------------------------- 0ca4ba59e2e3ed57f34cf239fc41b2471a8b8040 Jenkinsfile | 1 + 1 file changed, 1 insertion(+) diff --git a/Jenkinsfile b/Jenkinsfile index b2bd47a..9f93707 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -83,6 +83,7 @@ def buildGhc(params) { stage('Checkout') { checkout scm sh "git submodule update --init --recursive" + sh "${makeCmd} distclean" } stage('Configure') { From git at git.haskell.org Tue May 30 05:15:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 05:15:17 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Clean up treatment of tests (fdbf4b2) Message-ID: <20170530051517.784E63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/fdbf4b2df08de935403c510256633ae2ac66224b/ghc >--------------------------------------------------------------- commit fdbf4b2df08de935403c510256633ae2ac66224b Author: Ben Gamari Date: Tue May 30 01:10:56 2017 -0400 Clean up treatment of tests >--------------------------------------------------------------- fdbf4b2df08de935403c510256633ae2ac66224b Jenkinsfile | 80 +++++++++++++++++++++++++++++++++++++++---------------------- 1 file changed, 51 insertions(+), 29 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 9f93707..9420de6 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -6,41 +6,45 @@ properties( [ booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation'), booleanParam(name: 'nightly', defaultValue: false, description: 'are we building a nightly?'), - booleanParam(name: 'buildBindist', defaultValue: false, description: 'prepare and archive a binary distribution?'), booleanParam(name: 'runNofib', defaultValue: false, description: 'run nofib and archive results') ]) ]) parallel ( "linux x86-64" : { - node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib)} + node(label: 'linux && amd64') {buildAndTestGhc(targetTriple: 'x86_64-linux-gnu')} }, "linux x86-64 -> aarch64 unreg" : { - node(label: 'linux && amd64') {buildGhc(crossTarget: 'aarch64-linux-gnu', unreg: true)} + node(label: 'linux && amd64') {buildAndTestGhc(cross: true, targetTriple: 'aarch64-linux-gnu', unreg: true)} }, "linux x86-64 -> aarch64" : { - node(label: 'linux && amd64') {buildGhc(runNoFib: params.runNofib, crossTarget: 'aarch64-linux-gnu')} + node(label: 'linux && amd64') {buildGhc(cross: true, targetTriple: 'aarch64-linux-gnu')} + node(label: 'linux && aarch64') {testGhc(targetTriple: 'aarch64-linux-gnu')} }, "aarch64" : { - node(label: 'linux && aarch64') {buildGhc(runNoFib: false)} + node(label: 'linux && aarch64') {buildGhc(targetTriple: 'aarch64-linux-gnu')} }, "freebsd" : { node(label: 'freebsd && amd64') { - buildGhc(runNoFib: false, makeCmd: 'gmake', disableLargeAddrSpace: true) + buildGhc(targetTriple: 'x86_64-portbld-freebsd11.0', makeCmd: 'gmake', disableLargeAddrSpace: true) } }, // Requires cygpath plugin? "windows 64" : { node(label: 'windows && amd64') { - withMingw('MINGW64') { buildGhc(runNoFib: false) } + withMingw('MINGW64') { buildAndTestGhc(targetTriple: 'x86_64-w64-mingw32') } } }, "windows 32" : { node(label: 'windows && amd64') { - withMingw('MINGW64') { buildGhc(runNoFib: false) } + withMingw('MINGW32') { buildAndTestGhc(targetTriple: 'x86_64-pc-msys') } } }, - //"osx" : {node(label: 'darwin') {buildGhc(runNoFib: params.runNoFib)}} + /* + "osx" : { + node(label: 'darwin') {buildGhc(targetTriple: 'x86_64-apple-darwin16.0.0')} + } + */ ) def withMingw(String msystem, Closure f) { @@ -73,9 +77,14 @@ def installPackages(String[] pkgs) { sh "cabal install -j${env.THREADS} --with-compiler=`pwd`/inplace/bin/ghc-stage2 --package-db=`pwd`/inplace/lib/package.conf.d ${pkgs.join(' ')}" } +def buildAndTestGhc(params) { + buildGhc(params) + testGhc(params) +} + def buildGhc(params) { - boolean runNoFib = params?.runNofib ?: false - String crossTarget = params?.crossTarget + String targetTriple = params?.targetTriple + boolean cross = params?.crossTarget ?: false boolean unreg = params?.unreg ?: false boolean disableLargeAddrSpace = params?.disableLargeAddrSpace ?: false String makeCmd = params?.makeCmd ?: 'make' @@ -97,7 +106,7 @@ def buildGhc(params) { ValidateHpc=NO BUILD_DPH=NO """ - if (crossTarget) { + if (cross) { build_mk += """ # Cross compiling HADDOCK_DOCS=NO @@ -110,8 +119,8 @@ def buildGhc(params) { writeFile(file: 'mk/build.mk', text: build_mk) def configure_opts = ['--enable-tarballs-autodownload'] - if (crossTarget) { - configure_opts += '--target=${crossTarget}' + if (cross) { + configure_opts += '--target=${targetTriple}' } if (disableLargeAddrSpace) { configure_opts += '--disable-large-address-space' @@ -128,13 +137,35 @@ def buildGhc(params) { stage('Build') { sh "${makeCmd} -j${env.THREADS}" } + + stage('Prepare binary distribution') { + sh "${makeCmd} binary-dist" + def tarName = sh(script: "${makeCmd} -s echo VALUE=BIN_DIST_PREP_TAR_COMP", + returnStdout: true) + def ghcVersion = sh(script: "${makeCmd} -s echo VALUE=ProjectVersion") + writeFile "ghc-version" ghcVersion + archiveArtifacts "../${tarName}" + // Write a file so we can easily file the tarball and bindist directory later + stash(name: "bindist-${targetTriple}", includes: "ghc-version,../${tarName}") + } } def testGhc(params) { + String targetTriple = params?.targetTriple String makeCmd = params?.makeCmd ?: 'make' + boolean runNofib = params?.runNofib + + stage('Extract binary distribution') { + sh "mkdir tmp" + dir "tmp" + unstash "bindist-${targetTriple}" + def ghcVersion = readFile "ghc-version" + sh "tar -xf ${ghcVersion}-${targetTriple}.tar.xz" + dir ghcVersion + } stage('Install testsuite dependencies') { - if (params.nightly && !crossTarget) { + if (params.nightly) { def pkgs = ['mtl', 'parallel', 'parsec', 'primitive', 'QuickCheck', 'random', 'regex-compat', 'syb', 'stm', 'utf8-string', 'vector'] @@ -143,17 +174,15 @@ def testGhc(params) { } stage('Run testsuite') { - if (!crossTarget) { - def target = 'test' - if (params.nightly) { - target = 'slowtest' - } - sh "${makeCmd} THREADS=${env.THREADS} ${target}" + def target = 'test' + if (params.nightly) { + target = 'slowtest' } + sh "${makeCmd} THREADS=${env.THREADS} ${target}" } stage('Run nofib') { - if (runNofib && !crossTarget) { + if (runNofib) { installPkgs(['regex-compat']) sh """ cd nofib @@ -164,11 +193,4 @@ def testGhc(params) { archiveArtifacts 'nofib.log' } } - - stage('Prepare bindist') { - if (params.buildBindist) { - sh "${makeCmd} binary-dist" - archiveArtifacts 'ghc-*.tar.xz' - } - } } From git at git.haskell.org Tue May 30 11:49:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 11:49:26 +0000 (UTC) Subject: [commit: ghc] master: Efficient checks for stable modules (8bfab43) Message-ID: <20170530114926.1B9973A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8bfab438bdaa29b82c5ad57814bd60dcd02aa1c6/ghc >--------------------------------------------------------------- commit 8bfab438bdaa29b82c5ad57814bd60dcd02aa1c6 Author: Bartosz Nitka Date: Tue May 30 04:48:57 2017 -0700 Efficient checks for stable modules With a large number of modules in a home package (in my case 5000) the costs of linear lookups becomes significant. This changes them to efficient IntMap lookups. It reduces the cost of `:reload` on unchanged source from 5.77s to 1.62s on my test case. I could go further and make `Linker.unload` also take a set, but I prefer to concentrate on one thing at a time. Test Plan: harbormaster Reviewers: simonmar, austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3611 >--------------------------------------------------------------- 8bfab438bdaa29b82c5ad57814bd60dcd02aa1c6 compiler/main/GhcMake.hs | 56 ++++++++++++++++++++++++++++++++---------------- 1 file changed, 37 insertions(+), 19 deletions(-) diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs index a3b45e3..e11503b 100644 --- a/compiler/main/GhcMake.hs +++ b/compiler/main/GhcMake.hs @@ -305,7 +305,11 @@ load' how_much mHscMessage mod_graph = do -- Unload any modules which are going to be re-linked this time around. let stable_linkables = [ linkable - | m <- stable_obj++stable_bco, + | m <- nonDetEltsUniqSet stable_obj ++ + nonDetEltsUniqSet stable_bco, + -- It's OK to use nonDetEltsUniqSet here + -- because it only affects linking. Besides + -- this list only serves as a poor man's set. Just hmi <- [lookupHpt pruned_hpt m], Just linkable <- [hm_linkable hmi] ] liftIO $ unload hsc_env stable_linkables @@ -351,14 +355,18 @@ load' how_much mHscMessage mod_graph = do stable_mg = [ AcyclicSCC ms | AcyclicSCC ms <- full_mg, - ms_mod_name ms `elem` stable_obj++stable_bco ] + stable_mod_summary ms ] + + stable_mod_summary ms = + ms_mod_name ms `elementOfUniqSet` stable_obj || + ms_mod_name ms `elementOfUniqSet` stable_bco -- the modules from partial_mg that are not also stable -- NB. also keep cycles, we need to emit an error message later unstable_mg = filter not_stable partial_mg where not_stable (CyclicSCC _) = True not_stable (AcyclicSCC ms) - = ms_mod_name ms `notElem` stable_obj++stable_bco + = not $ stable_mod_summary ms -- Load all the stable modules first, before attempting to load -- an unstable module (#7231). @@ -579,7 +587,7 @@ guessOutputFile = modifySession $ \env -> -- compilation. pruneHomePackageTable :: HomePackageTable -> [ModSummary] - -> ([ModuleName],[ModuleName]) + -> StableModules -> HomePackageTable pruneHomePackageTable hpt summ (stable_obj, stable_bco) = mapHpt prune hpt @@ -596,7 +604,9 @@ pruneHomePackageTable hpt summ (stable_obj, stable_bco) ms_map = listToUFM [(ms_mod_name ms, ms) | ms <- summ] - is_stable m = m `elem` stable_obj || m `elem` stable_bco + is_stable m = + m `elementOfUniqSet` stable_obj || + m `elementOfUniqSet` stable_bco -- ----------------------------------------------------------------------------- -- @@ -679,18 +689,26 @@ unload hsc_env stable_linkables -- Unload everthing *except* 'stable_linkables' has changed. The current code in GhcMake handles this case fairly poorly, so be careful. -} + +type StableModules = + ( UniqSet ModuleName -- stableObject + , UniqSet ModuleName -- stableBCO + ) + + checkStability :: HomePackageTable -- HPT from last compilation -> [SCC ModSummary] -- current module graph (cyclic) -> UniqSet ModuleName -- all home modules - -> ([ModuleName], -- stableObject - [ModuleName]) -- stableBCO + -> StableModules -checkStability hpt sccs all_home_mods = foldl checkSCC ([],[]) sccs +checkStability hpt sccs all_home_mods = + foldl checkSCC (emptyUniqSet, emptyUniqSet) sccs where + checkSCC :: StableModules -> SCC ModSummary -> StableModules checkSCC (stable_obj, stable_bco) scc0 - | stableObjects = (scc_mods ++ stable_obj, stable_bco) - | stableBCOs = (stable_obj, scc_mods ++ stable_bco) + | stableObjects = (addListToUniqSet stable_obj scc_mods, stable_bco) + | stableBCOs = (stable_obj, addListToUniqSet stable_bco scc_mods) | otherwise = (stable_obj, stable_bco) where scc = flattenSCC scc0 @@ -701,8 +719,8 @@ checkStability hpt sccs all_home_mods = foldl checkSCC ([],[]) sccs scc_allimps = nub (filter home_module (concatMap ms_home_allimps scc)) -- all imports outside the current SCC, but in the home pkg - stable_obj_imps = map (`elem` stable_obj) scc_allimps - stable_bco_imps = map (`elem` stable_bco) scc_allimps + stable_obj_imps = map (`elementOfUniqSet` stable_obj) scc_allimps + stable_bco_imps = map (`elementOfUniqSet` stable_bco) scc_allimps stableObjects = and stable_obj_imps @@ -816,7 +834,7 @@ parUpsweep -- ^ The number of workers we wish to run in parallel -> Maybe Messager -> HomePackageTable - -> ([ModuleName],[ModuleName]) + -> StableModules -> (HscEnv -> IO ()) -> [SCC ModSummary] -> m (SuccessFlag, @@ -1026,8 +1044,8 @@ parUpsweep_one -- ^ The MVar that synchronizes updates to the global HscEnv -> IORef HomePackageTable -- ^ The old HPT - -> ([ModuleName],[ModuleName]) - -- ^ Lists of stable objects and BCOs + -> StableModules + -- ^ Sets of stable objects and BCOs -> Int -- ^ The index of this module -> Int @@ -1203,7 +1221,7 @@ upsweep :: GhcMonad m => Maybe Messager -> HomePackageTable -- ^ HPT from last time round (pruned) - -> ([ModuleName],[ModuleName]) -- ^ stable modules (see checkStability) + -> StableModules -- ^ stable modules (see checkStability) -> (HscEnv -> IO ()) -- ^ How to clean up unwanted tmp files -> [SCC ModSummary] -- ^ Mods to do (the worklist) -> m (SuccessFlag, @@ -1348,7 +1366,7 @@ maybeGetIfaceDate dflags location upsweep_mod :: HscEnv -> Maybe Messager -> HomePackageTable - -> ([ModuleName],[ModuleName]) + -> StableModules -> ModSummary -> Int -- index of module -> Int -- total number of modules @@ -1362,8 +1380,8 @@ upsweep_mod hsc_env mHscMessage old_hpt (stable_obj, stable_bco) summary mod_ind obj_fn = ml_obj_file (ms_location summary) hs_date = ms_hs_date summary - is_stable_obj = this_mod_name `elem` stable_obj - is_stable_bco = this_mod_name `elem` stable_bco + is_stable_obj = this_mod_name `elementOfUniqSet` stable_obj + is_stable_bco = this_mod_name `elementOfUniqSet` stable_bco old_hmi = lookupHpt old_hpt this_mod_name From git at git.haskell.org Tue May 30 14:43:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 14:43:26 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Handle documentation (d0cf2a1) Message-ID: <20170530144326.C7D9F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d0cf2a16ca5735413c2af6409e6b92aa9ee6f4b5/ghc >--------------------------------------------------------------- commit d0cf2a16ca5735413c2af6409e6b92aa9ee6f4b5 Author: Ben Gamari Date: Tue May 30 01:46:06 2017 -0400 Handle documentation >--------------------------------------------------------------- d0cf2a16ca5735413c2af6409e6b92aa9ee6f4b5 Jenkinsfile | 46 +++++++++++++++++++++++++++++++++++++++++++++- 1 file changed, 45 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 9420de6..4b7a9a5 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -12,7 +12,13 @@ properties( parallel ( "linux x86-64" : { - node(label: 'linux && amd64') {buildAndTestGhc(targetTriple: 'x86_64-linux-gnu')} + node(label: 'linux && amd64') { + buildAndTestGhc(targetTriple: 'x86_64-linux-gnu') + if (params.build_docs) { + updateReadTheDocs() + updateUsersGuide() + } + } }, "linux x86-64 -> aarch64 unreg" : { node(label: 'linux && amd64') {buildAndTestGhc(cross: true, targetTriple: 'aarch64-linux-gnu', unreg: true)} @@ -194,3 +200,41 @@ def testGhc(params) { } } } + +// Push update to ghc.readthedocs.org. +// Expects to be sitting in a build source tree. +def updateReadTheDocs() { + git clone 'git at github.com:bgamari/ghc-users-guide' + def commit = sh("git rev-parse HEAD", returnStdout=true) + sh """ + export GHC_TREE=$(pwd) + cd ghc-users-guide + ./export.sh + git commit -a -m "Update to ghc commit ${commit}" || true + git push + """ +} + +// Push update to downloads.haskell.org/~ghc/master/doc. +// Expects to be sitting in a configured source tree. +def updateUsersGuide() { + sh """ + $(makeCmd) html haddock EXTRA_HADDOCK_OPTS=--hyperlinked-sources + + out="$(mktemp -d)" + mkdir -p $out/libraries + echo $out + + cp -R docs/users_guide/build-html/users_guide $out/users-guide + for d in libraries/*; do + if [ ! -d $d/dist-install/doc ]; then continue; fi + mkdir -p $out/libraries/$(basename $d) + cp -R $d/dist-install/doc/*/* $out/libraries/$(basename $d) + done + cp -R libraries/*/dist-install/doc/* $out/libraries + chmod -R ugo+r $out + + rsync -az $out/ downloads.haskell.org:public_html/master + rm -R $out + """ +} From git at git.haskell.org Tue May 30 14:43:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 14:43:29 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarball generation (a206fb7) Message-ID: <20170530144329.816353A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a206fb7df1f71ba8b1f18043b9e0818933b5ca0e/ghc >--------------------------------------------------------------- commit a206fb7df1f71ba8b1f18043b9e0818933b5ca0e Author: Ben Gamari Date: Tue May 30 10:43:09 2017 -0400 Fix tarball generation >--------------------------------------------------------------- a206fb7df1f71ba8b1f18043b9e0818933b5ca0e Jenkinsfile | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 4b7a9a5..97ff67a 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -148,8 +148,9 @@ def buildGhc(params) { sh "${makeCmd} binary-dist" def tarName = sh(script: "${makeCmd} -s echo VALUE=BIN_DIST_PREP_TAR_COMP", returnStdout: true) - def ghcVersion = sh(script: "${makeCmd} -s echo VALUE=ProjectVersion") - writeFile "ghc-version" ghcVersion + def ghcVersion = sh(script: "${makeCmd} -s echo VALUE=ProjectVersion", + returnStdout: true) + writeFile(file: "ghc-version", text: ghcVersion) archiveArtifacts "../${tarName}" // Write a file so we can easily file the tarball and bindist directory later stash(name: "bindist-${targetTriple}", includes: "ghc-version,../${tarName}") From git at git.haskell.org Tue May 30 14:45:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 14:45:02 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarball generation (6282d63) Message-ID: <20170530144502.6DB1C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/6282d636e1af723e596c4af25902ed81249f0984/ghc >--------------------------------------------------------------- commit 6282d636e1af723e596c4af25902ed81249f0984 Author: Ben Gamari Date: Tue May 30 10:43:09 2017 -0400 Fix tarball generation >--------------------------------------------------------------- 6282d636e1af723e596c4af25902ed81249f0984 Jenkinsfile | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 4b7a9a5..29902ed 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -148,8 +148,9 @@ def buildGhc(params) { sh "${makeCmd} binary-dist" def tarName = sh(script: "${makeCmd} -s echo VALUE=BIN_DIST_PREP_TAR_COMP", returnStdout: true) - def ghcVersion = sh(script: "${makeCmd} -s echo VALUE=ProjectVersion") - writeFile "ghc-version" ghcVersion + def ghcVersion = sh(script: "${makeCmd} -s echo VALUE=ProjectVersion", + returnStdout: true) + writeFile(file: "ghc-version", text: ghcVersion) archiveArtifacts "../${tarName}" // Write a file so we can easily file the tarball and bindist directory later stash(name: "bindist-${targetTriple}", includes: "ghc-version,../${tarName}") @@ -205,7 +206,7 @@ def testGhc(params) { // Expects to be sitting in a build source tree. def updateReadTheDocs() { git clone 'git at github.com:bgamari/ghc-users-guide' - def commit = sh("git rev-parse HEAD", returnStdout=true) + def commit = sh(script: "git rev-parse HEAD", returnStdout=true) sh """ export GHC_TREE=$(pwd) cd ghc-users-guide From git at git.haskell.org Tue May 30 14:46:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 14:46:03 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix documentation (32878ff) Message-ID: <20170530144603.8839C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/32878ff67e84f75383c0a9bc4ac824e85b953a77/ghc >--------------------------------------------------------------- commit 32878ff67e84f75383c0a9bc4ac824e85b953a77 Author: Ben Gamari Date: Tue May 30 10:45:52 2017 -0400 Fix documentation >--------------------------------------------------------------- 32878ff67e84f75383c0a9bc4ac824e85b953a77 Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 29902ed..8d645c5 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -211,7 +211,7 @@ def updateReadTheDocs() { export GHC_TREE=$(pwd) cd ghc-users-guide ./export.sh - git commit -a -m "Update to ghc commit ${commit}" || true + git commit -a -m \"Update to ghc commit ${commit}\" || true git push """ } From git at git.haskell.org Tue May 30 14:46:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 14:46:44 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix documentation (78d7905) Message-ID: <20170530144644.7F6EF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/78d79053815bac9d192aee2f5971a69e0480d2d7/ghc >--------------------------------------------------------------- commit 78d79053815bac9d192aee2f5971a69e0480d2d7 Author: Ben Gamari Date: Tue May 30 10:45:52 2017 -0400 Fix documentation >--------------------------------------------------------------- 78d79053815bac9d192aee2f5971a69e0480d2d7 Jenkinsfile | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 29902ed..3d65c6a 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -208,10 +208,10 @@ def updateReadTheDocs() { git clone 'git at github.com:bgamari/ghc-users-guide' def commit = sh(script: "git rev-parse HEAD", returnStdout=true) sh """ - export GHC_TREE=$(pwd) + export GHC_TREE=\$(pwd) cd ghc-users-guide ./export.sh - git commit -a -m "Update to ghc commit ${commit}" || true + git commit -a -m \"Update to ghc commit ${commit}\" || true git push """ } From git at git.haskell.org Tue May 30 14:47:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 14:47:03 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix documentation (9587ed7) Message-ID: <20170530144703.7CA123A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9587ed70c23039b939a16a2fcd5dcf9af419221d/ghc >--------------------------------------------------------------- commit 9587ed70c23039b939a16a2fcd5dcf9af419221d Author: Ben Gamari Date: Tue May 30 10:45:52 2017 -0400 Fix documentation >--------------------------------------------------------------- 9587ed70c23039b939a16a2fcd5dcf9af419221d Jenkinsfile | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 29902ed..1731629 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -206,12 +206,12 @@ def testGhc(params) { // Expects to be sitting in a build source tree. def updateReadTheDocs() { git clone 'git at github.com:bgamari/ghc-users-guide' - def commit = sh(script: "git rev-parse HEAD", returnStdout=true) + def commit = sh(script: "git rev-parse HEAD", returnStdout: true) sh """ - export GHC_TREE=$(pwd) + export GHC_TREE=\$(pwd) cd ghc-users-guide ./export.sh - git commit -a -m "Update to ghc commit ${commit}" || true + git commit -a -m \"Update to ghc commit ${commit}\" || true git push """ } From git at git.haskell.org Tue May 30 14:48:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 14:48:25 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix documentation (054a4bf) Message-ID: <20170530144825.C853A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/054a4bf164670bf5488eae30b0cafebbe7499324/ghc >--------------------------------------------------------------- commit 054a4bf164670bf5488eae30b0cafebbe7499324 Author: Ben Gamari Date: Tue May 30 10:45:52 2017 -0400 Fix documentation >--------------------------------------------------------------- 054a4bf164670bf5488eae30b0cafebbe7499324 Jenkinsfile | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 29902ed..3fdf815 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -206,12 +206,12 @@ def testGhc(params) { // Expects to be sitting in a build source tree. def updateReadTheDocs() { git clone 'git at github.com:bgamari/ghc-users-guide' - def commit = sh(script: "git rev-parse HEAD", returnStdout=true) + def commit = sh(script: "git rev-parse HEAD", returnStdout: true) sh """ - export GHC_TREE=$(pwd) + export GHC_TREE=\$(pwd) cd ghc-users-guide ./export.sh - git commit -a -m "Update to ghc commit ${commit}" || true + git commit -a -m \"Update to ghc commit ${commit}\" || true git push """ } @@ -220,9 +220,9 @@ def updateReadTheDocs() { // Expects to be sitting in a configured source tree. def updateUsersGuide() { sh """ - $(makeCmd) html haddock EXTRA_HADDOCK_OPTS=--hyperlinked-sources + ${makeCmd} html haddock EXTRA_HADDOCK_OPTS=--hyperlinked-sources - out="$(mktemp -d)" + out=\"$(mktemp -d)\" mkdir -p $out/libraries echo $out From git at git.haskell.org Tue May 30 14:50:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 14:50:38 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix documentation (e1f421c) Message-ID: <20170530145038.194EE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/e1f421c8427209929e5430c88418a4ce67cdc6b3/ghc >--------------------------------------------------------------- commit e1f421c8427209929e5430c88418a4ce67cdc6b3 Author: Ben Gamari Date: Tue May 30 10:45:52 2017 -0400 Fix documentation >--------------------------------------------------------------- e1f421c8427209929e5430c88418a4ce67cdc6b3 Jenkinsfile | 16 +++++++--------- 1 file changed, 7 insertions(+), 9 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 29902ed..c88b5ee 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -206,12 +206,12 @@ def testGhc(params) { // Expects to be sitting in a build source tree. def updateReadTheDocs() { git clone 'git at github.com:bgamari/ghc-users-guide' - def commit = sh(script: "git rev-parse HEAD", returnStdout=true) + def commit = sh(script: "git rev-parse HEAD", returnStdout: true) sh """ - export GHC_TREE=$(pwd) + export GHC_TREE=\$(pwd) cd ghc-users-guide ./export.sh - git commit -a -m "Update to ghc commit ${commit}" || true + git commit -a -m \"Update to ghc commit ${commit}\" || true git push """ } @@ -219,23 +219,21 @@ def updateReadTheDocs() { // Push update to downloads.haskell.org/~ghc/master/doc. // Expects to be sitting in a configured source tree. def updateUsersGuide() { - sh """ - $(makeCmd) html haddock EXTRA_HADDOCK_OPTS=--hyperlinked-sources - + sh "${makeCmd} html haddock EXTRA_HADDOCK_OPTS=--hyperlinked-sources" + sh ''' out="$(mktemp -d)" mkdir -p $out/libraries - echo $out cp -R docs/users_guide/build-html/users_guide $out/users-guide for d in libraries/*; do if [ ! -d $d/dist-install/doc ]; then continue; fi mkdir -p $out/libraries/$(basename $d) - cp -R $d/dist-install/doc/*/* $out/libraries/$(basename $d) + cp -R $d/dist-install/doc/*/* $out/libraries/\$(basename \$d) done cp -R libraries/*/dist-install/doc/* $out/libraries chmod -R ugo+r $out rsync -az $out/ downloads.haskell.org:public_html/master rm -R $out - """ + ''' } From git at git.haskell.org Tue May 30 16:11:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 16:11:29 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix testsuite (7293f6d) Message-ID: <20170530161129.D09433A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7293f6d50e574fccb3958135bf35b3901af4e7c6/ghc >--------------------------------------------------------------- commit 7293f6d50e574fccb3958135bf35b3901af4e7c6 Author: Ben Gamari Date: Tue May 30 12:11:16 2017 -0400 Fix testsuite >--------------------------------------------------------------- 7293f6d50e574fccb3958135bf35b3901af4e7c6 Jenkinsfile | 64 ++++++++++++++++++++++++++++++------------------------------- 1 file changed, 32 insertions(+), 32 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index c88b5ee..2e18d93 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -157,47 +157,47 @@ def buildGhc(params) { } } +def withGhcBinDist(String targetTriple, Closure f) { + unstash "bindist-${targetTriple}" + def ghcVersion = readFile "ghc-version" + sh "tar -xf ${ghcVersion}-${targetTriple}.tar.xz" + dir("ghc-${ghcVersion}") { f } +} + def testGhc(params) { String targetTriple = params?.targetTriple String makeCmd = params?.makeCmd ?: 'make' boolean runNofib = params?.runNofib - stage('Extract binary distribution') { - sh "mkdir tmp" - dir "tmp" - unstash "bindist-${targetTriple}" - def ghcVersion = readFile "ghc-version" - sh "tar -xf ${ghcVersion}-${targetTriple}.tar.xz" - dir ghcVersion - } - - stage('Install testsuite dependencies') { - if (params.nightly) { - def pkgs = ['mtl', 'parallel', 'parsec', 'primitive', 'QuickCheck', - 'random', 'regex-compat', 'syb', 'stm', 'utf8-string', - 'vector'] - installPkgs pkgs + withGhcBinDist(targetTriple) { + stage('Install testsuite dependencies') { + if (params.nightly) { + def pkgs = ['mtl', 'parallel', 'parsec', 'primitive', 'QuickCheck', + 'random', 'regex-compat', 'syb', 'stm', 'utf8-string', + 'vector'] + installPkgs pkgs + } } - } - stage('Run testsuite') { - def target = 'test' - if (params.nightly) { - target = 'slowtest' + stage('Run testsuite') { + def target = 'test' + if (params.nightly) { + target = 'slowtest' + } + sh "${makeCmd} THREADS=${env.THREADS} ${target}" } - sh "${makeCmd} THREADS=${env.THREADS} ${target}" - } - stage('Run nofib') { - if (runNofib) { - installPkgs(['regex-compat']) - sh """ - cd nofib - ${makeCmd} clean - ${makeCmd} boot - ${makeCmd} >../nofib.log 2>&1 - """ - archiveArtifacts 'nofib.log' + stage('Run nofib') { + if (runNofib) { + installPkgs(['regex-compat']) + sh """ + cd nofib + ${makeCmd} clean + ${makeCmd} boot + ${makeCmd} >../nofib.log 2>&1 + """ + archiveArtifacts 'nofib.log' + } } } } From git at git.haskell.org Tue May 30 17:57:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 17:57:32 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix test (644d9fb) Message-ID: <20170530175732.B7D453A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/644d9fbd35770795bd64475127e38930cb6f6bb8/ghc >--------------------------------------------------------------- commit 644d9fbd35770795bd64475127e38930cb6f6bb8 Author: Ben Gamari Date: Tue May 30 13:57:23 2017 -0400 Fix test >--------------------------------------------------------------- 644d9fbd35770795bd64475127e38930cb6f6bb8 Jenkinsfile | 39 ++++++++++++++++++++++++++++----------- 1 file changed, 28 insertions(+), 11 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 2e18d93..45aae0c 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -146,22 +146,35 @@ def buildGhc(params) { stage('Prepare binary distribution') { sh "${makeCmd} binary-dist" - def tarName = sh(script: "${makeCmd} -s echo VALUE=BIN_DIST_PREP_TAR_COMP", - returnStdout: true) - def ghcVersion = sh(script: "${makeCmd} -s echo VALUE=ProjectVersion", - returnStdout: true) - writeFile(file: "ghc-version", text: ghcVersion) - archiveArtifacts "../${tarName}" + writeJSON(file: 'bindist.json', json: { + commit: resolveCommitSha('HEAD') + tarName: getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') + dirName: getMakeValue(makeCmd, 'BIN_DIST_NAME') + ghcVersion: getMakeValue(makeCmd, 'ProjectVersion') + targetPlatform: getMakeValue(makeCmd, 'TARGETPLATFORM') + }) + sh 'pwd; ls' // Write a file so we can easily file the tarball and bindist directory later - stash(name: "bindist-${targetTriple}", includes: "ghc-version,../${tarName}") + stash(name: "bindist-${targetTriple}", includes: "bindist.json,${tarName}") + archiveArtifacts "${tarName}" } } +def getMakeValue(String makeCmd, String value) { + return sh(script: "${makeCmd} -s echo VALUE=${value}", returnStdout: true) +} + def withGhcBinDist(String targetTriple, Closure f) { unstash "bindist-${targetTriple}" - def ghcVersion = readFile "ghc-version" - sh "tar -xf ${ghcVersion}-${targetTriple}.tar.xz" - dir("ghc-${ghcVersion}") { f } + def metadata = readJSON "bindist.json" + sh "tar -xf ${metadata.tarName}" + dir("${metadata.bindistName}") { + try { + f + } finally { + deleteDir() + } + } } def testGhc(params) { @@ -202,11 +215,15 @@ def testGhc(params) { } } +def resolveCommitSha(String ref) { + return sh(script: "git rev-parse ${ref}", returnStdout: true) +} + // Push update to ghc.readthedocs.org. // Expects to be sitting in a build source tree. def updateReadTheDocs() { git clone 'git at github.com:bgamari/ghc-users-guide' - def commit = sh(script: "git rev-parse HEAD", returnStdout: true) + def commit = resolveCommitSha('HEAD') sh """ export GHC_TREE=\$(pwd) cd ghc-users-guide From git at git.haskell.org Tue May 30 20:04:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 May 2017 20:04:54 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Be more explicit (6f1cfb1) Message-ID: <20170530200454.683FE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/6f1cfb15b1b1ec852182bdba0ce995c44efda037/ghc >--------------------------------------------------------------- commit 6f1cfb15b1b1ec852182bdba0ce995c44efda037 Author: Ben Gamari Date: Tue May 30 16:04:31 2017 -0400 Be more explicit >--------------------------------------------------------------- 6f1cfb15b1b1ec852182bdba0ce995c44efda037 Jenkinsfile | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 45aae0c..d6122ef 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,5 +1,11 @@ #!groovy +/* + Dependencies: + * Pipeline Utility steps plugin + +*/ + properties( [ parameters( @@ -166,7 +172,7 @@ def getMakeValue(String makeCmd, String value) { def withGhcBinDist(String targetTriple, Closure f) { unstash "bindist-${targetTriple}" - def metadata = readJSON "bindist.json" + def metadata = readJSON file: "bindist.json" sh "tar -xf ${metadata.tarName}" dir("${metadata.bindistName}") { try { From git at git.haskell.org Wed May 31 12:28:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 31 May 2017 12:28:12 +0000 (UTC) Subject: [commit: ghc] master: Faster checkFamInstConsistency (69d9081) Message-ID: <20170531122812.B32523A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/69d9081d9fa3ff36fda36e4e11ef7e8f946ecf2a/ghc >--------------------------------------------------------------- commit 69d9081d9fa3ff36fda36e4e11ef7e8f946ecf2a Author: Bartosz Nitka Date: Fri May 19 08:08:01 2017 -0700 Faster checkFamInstConsistency This implements the idea from https://ghc.haskell.org/trac/ghc/ticket/13092#comment:14. It's explained in Note [Checking family instance optimization] in more detail. This improves the test case T13719 tenfold and cuts down the compile time on `:load` in `ghci` on our internal code base by half. Test Plan: ./validate Reviewers: simonpj, simonmar, rwbarton, austin, bgamari Reviewed By: simonpj Subscribers: thomie GHC Trac Issues: #13719 Differential Revision: https://phabricator.haskell.org/D3603 >--------------------------------------------------------------- 69d9081d9fa3ff36fda36e4e11ef7e8f946ecf2a compiler/typecheck/FamInst.hs | 212 +++++++++++++++++++++--------------- compiler/typecheck/TcRnDriver.hs | 2 +- testsuite/tests/perf/compiler/all.T | 6 +- testsuite/tests/perf/haddock/all.T | 6 +- 4 files changed, 135 insertions(+), 91 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 69d9081d9fa3ff36fda36e4e11ef7e8f946ecf2a From git at git.haskell.org Wed May 31 14:43:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 31 May 2017 14:43:42 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix JSON serialization (1e55852) Message-ID: <20170531144342.F0BFF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/1e558525120b5d035af04f504fc8c0e0e41ab728/ghc >--------------------------------------------------------------- commit 1e558525120b5d035af04f504fc8c0e0e41ab728 Author: Ben Gamari Date: Wed May 31 10:43:24 2017 -0400 Fix JSON serialization >--------------------------------------------------------------- 1e558525120b5d035af04f504fc8c0e0e41ab728 Jenkinsfile | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index d6122ef..ad6df30 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -152,13 +152,13 @@ def buildGhc(params) { stage('Prepare binary distribution') { sh "${makeCmd} binary-dist" - writeJSON(file: 'bindist.json', json: { - commit: resolveCommitSha('HEAD') - tarName: getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') - dirName: getMakeValue(makeCmd, 'BIN_DIST_NAME') - ghcVersion: getMakeValue(makeCmd, 'ProjectVersion') - targetPlatform: getMakeValue(makeCmd, 'TARGETPLATFORM') - }) + def json = new JSONObject() + json.put('commit', resolveCommitSha('HEAD')) + json.put('tarName', getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP')) + json.put('dirName', getMakeValue(makeCmd, 'BIN_DIST_NAME')) + json.put('ghcVersion', getMakeValue(makeCmd, 'ProjectVersion')) + json.put('targetPlatform', getMakeValue(makeCmd, 'TARGETPLATFORM')) + writeJSON(file: 'bindist.json', json: json) sh 'pwd; ls' // Write a file so we can easily file the tarball and bindist directory later stash(name: "bindist-${targetTriple}", includes: "bindist.json,${tarName}") From git at git.haskell.org Wed May 31 14:47:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 31 May 2017 14:47:48 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix JSON serialization (781e0b1) Message-ID: <20170531144748.D930E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/781e0b1bac08ff572f0691a865646b7046bc8e18/ghc >--------------------------------------------------------------- commit 781e0b1bac08ff572f0691a865646b7046bc8e18 Author: Ben Gamari Date: Wed May 31 10:43:24 2017 -0400 Fix JSON serialization >--------------------------------------------------------------- 781e0b1bac08ff572f0691a865646b7046bc8e18 Jenkinsfile | 16 +++++++++------- 1 file changed, 9 insertions(+), 7 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index d6122ef..7df1f02 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -6,6 +6,8 @@ */ +import net.sf.json.JSONObject + properties( [ parameters( @@ -152,13 +154,13 @@ def buildGhc(params) { stage('Prepare binary distribution') { sh "${makeCmd} binary-dist" - writeJSON(file: 'bindist.json', json: { - commit: resolveCommitSha('HEAD') - tarName: getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') - dirName: getMakeValue(makeCmd, 'BIN_DIST_NAME') - ghcVersion: getMakeValue(makeCmd, 'ProjectVersion') - targetPlatform: getMakeValue(makeCmd, 'TARGETPLATFORM') - }) + def json = new JSONObject() + json.put('commit', resolveCommitSha('HEAD')) + json.put('tarName', getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP')) + json.put('dirName', getMakeValue(makeCmd, 'BIN_DIST_NAME')) + json.put('ghcVersion', getMakeValue(makeCmd, 'ProjectVersion')) + json.put('targetPlatform', getMakeValue(makeCmd, 'TARGETPLATFORM')) + writeJSON(file: 'bindist.json', json: json) sh 'pwd; ls' // Write a file so we can easily file the tarball and bindist directory later stash(name: "bindist-${targetTriple}", includes: "bindist.json,${tarName}") From git at git.haskell.org Wed May 31 15:36:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 31 May 2017 15:36:21 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix missing binding (b0f36fc) Message-ID: <20170531153621.831A53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/b0f36fc32b088787e7ce22b115f1ab3faec6b730/ghc >--------------------------------------------------------------- commit b0f36fc32b088787e7ce22b115f1ab3faec6b730 Author: Ben Gamari Date: Wed May 31 11:36:00 2017 -0400 Fix missing binding >--------------------------------------------------------------- b0f36fc32b088787e7ce22b115f1ab3faec6b730 Jenkinsfile | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 7df1f02..605a635 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -155,8 +155,9 @@ def buildGhc(params) { stage('Prepare binary distribution') { sh "${makeCmd} binary-dist" def json = new JSONObject() + def tarName = getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') json.put('commit', resolveCommitSha('HEAD')) - json.put('tarName', getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP')) + json.put('tarName', tarName) json.put('dirName', getMakeValue(makeCmd, 'BIN_DIST_NAME')) json.put('ghcVersion', getMakeValue(makeCmd, 'ProjectVersion')) json.put('targetPlatform', getMakeValue(makeCmd, 'TARGETPLATFORM')) From git at git.haskell.org Wed May 31 18:57:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 31 May 2017 18:57:46 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (0c7c876) Message-ID: <20170531185746.52B4B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0c7c87608ffdeedcae244573c581444e4fdbc021/ghc >--------------------------------------------------------------- commit 0c7c87608ffdeedcae244573c581444e4fdbc021 Author: Ben Gamari Date: Wed May 31 14:57:34 2017 -0400 Debug >--------------------------------------------------------------- 0c7c87608ffdeedcae244573c581444e4fdbc021 Jenkinsfile | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 605a635..82aebbb 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -106,7 +106,7 @@ def buildGhc(params) { stage('Checkout') { checkout scm sh "git submodule update --init --recursive" - sh "${makeCmd} distclean" + //sh "${makeCmd} distclean" } stage('Configure') { @@ -155,7 +155,8 @@ def buildGhc(params) { stage('Prepare binary distribution') { sh "${makeCmd} binary-dist" def json = new JSONObject() - def tarName = getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') + def tarPath = getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') + def tarName = sh "basename ${tarPath}" json.put('commit', resolveCommitSha('HEAD')) json.put('tarName', tarName) json.put('dirName', getMakeValue(makeCmd, 'BIN_DIST_NAME')) @@ -176,6 +177,7 @@ def getMakeValue(String makeCmd, String value) { def withGhcBinDist(String targetTriple, Closure f) { unstash "bindist-${targetTriple}" def metadata = readJSON file: "bindist.json" + sh 'cat bindist.json' sh "tar -xf ${metadata.tarName}" dir("${metadata.bindistName}") { try { From git at git.haskell.org Wed May 31 20:11:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 31 May 2017 20:11:03 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (df6fa3f) Message-ID: <20170531201103.816D93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/df6fa3fd79c8aba7eb75505dba1c0ccc48789a85/ghc >--------------------------------------------------------------- commit df6fa3fd79c8aba7eb75505dba1c0ccc48789a85 Author: Ben Gamari Date: Wed May 31 14:57:34 2017 -0400 Debug >--------------------------------------------------------------- df6fa3fd79c8aba7eb75505dba1c0ccc48789a85 Jenkinsfile | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 605a635..151bc7b 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -106,7 +106,7 @@ def buildGhc(params) { stage('Checkout') { checkout scm sh "git submodule update --init --recursive" - sh "${makeCmd} distclean" + //sh "${makeCmd} distclean" } stage('Configure') { @@ -155,14 +155,15 @@ def buildGhc(params) { stage('Prepare binary distribution') { sh "${makeCmd} binary-dist" def json = new JSONObject() - def tarName = getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') + def tarPath = getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') + def tarName = sh "basename ${tarPath}" json.put('commit', resolveCommitSha('HEAD')) json.put('tarName', tarName) json.put('dirName', getMakeValue(makeCmd, 'BIN_DIST_NAME')) json.put('ghcVersion', getMakeValue(makeCmd, 'ProjectVersion')) json.put('targetPlatform', getMakeValue(makeCmd, 'TARGETPLATFORM')) writeJSON(file: 'bindist.json', json: json) - sh 'pwd; ls' + sh 'cat bindist.json' // Write a file so we can easily file the tarball and bindist directory later stash(name: "bindist-${targetTriple}", includes: "bindist.json,${tarName}") archiveArtifacts "${tarName}" @@ -176,6 +177,7 @@ def getMakeValue(String makeCmd, String value) { def withGhcBinDist(String targetTriple, Closure f) { unstash "bindist-${targetTriple}" def metadata = readJSON file: "bindist.json" + sh 'cat bindist.json' sh "tar -xf ${metadata.tarName}" dir("${metadata.bindistName}") { try { From git at git.haskell.org Wed May 31 20:26:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 31 May 2017 20:26:52 +0000 (UTC) Subject: [commit: ghc] wip/new-tree-one-param-2: Udate hsSyn AST to use Trees that Grow (0c00097) Message-ID: <20170531202652.58A423A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-tree-one-param-2 Link : http://ghc.haskell.org/trac/ghc/changeset/0c000974ece044b6f185c7166b10e4bb92b66048/ghc >--------------------------------------------------------------- commit 0c000974ece044b6f185c7166b10e4bb92b66048 Author: Alan Zimmerman Date: Fri May 19 14:56:09 2017 +0200 Udate hsSyn AST to use Trees that Grow Summary: See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow This commit prepares the ground for a full extensible AST, by replacing the type parameter for the hsSyn data types with a set of indices into type families, data GhcPs -- ^ Index for GHC parser output data GhcRn -- ^ Index for GHC renamer output data GhcTc -- ^ Index for GHC typechecker output These are now used instead of `RdrName`, `Name` and `Id`/`TcId`/`Var` Where the original name type is required in a polymorphic context, this is accessible via the IdP type family, defined as type family IdP p type instance IdP GhcPs = RdrName type instance IdP GhcRn = Name type instance IdP GhcTc = Id These types are declared in the new 'hsSyn/HsExtension.hs' module. To gain a better understanding of the extension mechanism, it has been applied to `HsLit` only, also replacing the `SourceText` fields in them with extension types. To preserve extension generality, a type class is introduced to capture the `SourceText` interface, which must be honoured by all of the extension points which originally had a `SourceText`. The class is defined as class HasSourceText a where -- Provide setters to mimic existing constructors noSourceText :: a sourceText :: String -> a setSourceText :: SourceText -> a getSourceText :: a -> SourceText And the constraint is captured in `SourceTextX`, which is a constraint type listing all the extension points that make use of the class. Updating Haddock submodule to match. Test Plan: ./validate Reviewers: simonpj, shayan-najd, goldfire, austin, bgamari Subscribers: rwbarton, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D3609 >--------------------------------------------------------------- 0c000974ece044b6f185c7166b10e4bb92b66048 compiler/backpack/BkpSyn.hs | 3 +- compiler/backpack/DriverBkp.hs | 4 +- compiler/deSugar/Check.hs | 66 +-- compiler/deSugar/Coverage.hs | 122 ++--- compiler/deSugar/Desugar.hs | 7 +- compiler/deSugar/DsArrows.hs | 71 +-- compiler/deSugar/DsBinds.hs | 16 +- compiler/deSugar/DsExpr.hs | 41 +- compiler/deSugar/DsExpr.hs-boot | 16 +- compiler/deSugar/DsForeign.hs | 10 +- compiler/deSugar/DsGRHSs.hs | 18 +- compiler/deSugar/DsListComp.hs | 59 +-- compiler/deSugar/DsMeta.hs | 231 ++++----- compiler/deSugar/DsMonad.hs | 2 +- compiler/deSugar/DsUtils.hs | 29 +- compiler/deSugar/Match.hs | 43 +- compiler/deSugar/Match.hs-boot | 9 +- compiler/deSugar/MatchCon.hs | 8 +- compiler/deSugar/MatchLit.hs | 40 +- compiler/deSugar/PmExpr.hs | 12 +- compiler/ghc.cabal.in | 1 + compiler/ghc.mk | 1 + compiler/hsSyn/Convert.hs | 149 +++--- compiler/hsSyn/HsBinds.hs | 121 ++--- compiler/hsSyn/HsDecls.hs | 531 +++++++++++---------- compiler/hsSyn/HsDumpAst.hs | 28 +- compiler/hsSyn/HsExpr.hs | 461 +++++++++--------- compiler/hsSyn/HsExpr.hs-boot | 40 +- compiler/hsSyn/HsExtension.hs | 267 +++++++++++ compiler/hsSyn/HsImpExp.hs | 37 +- compiler/hsSyn/HsLit.hs | 132 +++-- compiler/hsSyn/HsPat.hs | 183 +++---- compiler/hsSyn/HsPat.hs-boot | 6 +- compiler/hsSyn/HsSyn.hs | 7 +- compiler/hsSyn/HsTypes.hs | 392 +++++++-------- compiler/hsSyn/HsUtils.hs | 297 ++++++------ compiler/hsSyn/PlaceHolder.hs | 50 -- compiler/main/GHC.hs | 8 +- compiler/main/HeaderInfo.hs | 7 +- compiler/main/Hooks.hs | 28 +- compiler/main/HscMain.hs | 16 +- compiler/main/HscStats.hs | 3 +- compiler/main/HscTypes.hs | 34 +- compiler/main/InteractiveEval.hs | 10 +- compiler/parser/Parser.y | 373 ++++++++------- compiler/parser/RdrHsSyn.hs | 245 +++++----- compiler/rename/RnBinds.hs | 150 +++--- compiler/rename/RnEnv.hs | 29 +- compiler/rename/RnExpr.hs | 226 ++++----- compiler/rename/RnExpr.hs-boot | 22 +- compiler/rename/RnFixity.hs | 2 +- compiler/rename/RnNames.hs | 87 ++-- compiler/rename/RnPat.hs | 64 +-- compiler/rename/RnSource.hs | 187 ++++---- compiler/rename/RnSplice.hs | 63 +-- compiler/rename/RnSplice.hs-boot | 12 +- compiler/rename/RnTypes.hs | 211 ++++---- compiler/rename/RnUtils.hs | 2 +- compiler/typecheck/Inst.hs | 29 +- compiler/typecheck/TcAnnotations.hs | 17 +- compiler/typecheck/TcArrows.hs | 19 +- compiler/typecheck/TcBackpack.hs | 1 + compiler/typecheck/TcBinds.hs | 96 ++-- compiler/typecheck/TcClassDcl.hs | 41 +- compiler/typecheck/TcDefaults.hs | 8 +- compiler/typecheck/TcDeriv.hs | 39 +- compiler/typecheck/TcDerivUtils.hs | 8 +- compiler/typecheck/TcEnv.hs | 18 +- compiler/typecheck/TcEnv.hs-boot | 1 + compiler/typecheck/TcExpr.hs | 146 +++--- compiler/typecheck/TcExpr.hs-boot | 31 +- compiler/typecheck/TcForeign.hs | 23 +- compiler/typecheck/TcGenDeriv.hs | 151 +++--- compiler/typecheck/TcGenFunctor.hs | 99 ++-- compiler/typecheck/TcGenGenerics.hs | 32 +- compiler/typecheck/TcHsSyn.hs | 137 +++--- compiler/typecheck/TcHsType.hs | 93 ++-- compiler/typecheck/TcInstDcls.hs | 72 +-- compiler/typecheck/TcInstDcls.hs-boot | 5 +- compiler/typecheck/TcMatches.hs | 106 ++-- compiler/typecheck/TcMatches.hs-boot | 11 +- compiler/typecheck/TcPat.hs | 53 +- compiler/typecheck/TcPatSyn.hs | 86 ++-- compiler/typecheck/TcPatSyn.hs-boot | 13 +- compiler/typecheck/TcRnDriver.hs | 63 +-- compiler/typecheck/TcRnExports.hs | 41 +- compiler/typecheck/TcRnTypes.hs | 73 +-- compiler/typecheck/TcRules.hs | 10 +- compiler/typecheck/TcSigs.hs | 34 +- compiler/typecheck/TcSplice.hs | 53 +- compiler/typecheck/TcSplice.hs-boot | 36 +- compiler/typecheck/TcTyClsDecls.hs | 112 ++--- compiler/typecheck/TcTyDecls.hs | 11 +- compiler/typecheck/TcTypeable.hs | 55 +-- compiler/typecheck/TcUnify.hs | 11 +- compiler/typecheck/TcUnify.hs-boot | 14 +- compiler/typecheck/TcValidity.hs | 2 +- ghc/GHCi/UI.hs | 6 +- ghc/GHCi/UI/Info.hs | 6 +- ghc/GHCi/UI/Monad.hs | 7 +- .../tests/ghc-api/annotations-literals/parsed.hs | 6 +- testsuite/tests/ghc-api/annotations/parseTree.hs | 2 +- .../tests/ghc-api/annotations/stringSource.hs | 6 +- testsuite/tests/ghc-api/annotations/t11430.hs | 4 +- testsuite/tests/quasiquotation/T7918.hs | 6 +- utils/ghctags/Main.hs | 5 +- utils/haddock | 2 +- 107 files changed, 3861 insertions(+), 3328 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 0c000974ece044b6f185c7166b10e4bb92b66048 From git at git.haskell.org Wed May 31 20:26:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 31 May 2017 20:26:54 +0000 (UTC) Subject: [commit: ghc] wip/new-tree-one-param-2's head updated: Udate hsSyn AST to use Trees that Grow (0c00097) Message-ID: <20170531202654.AE9B03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/new-tree-one-param-2' now includes: b5c73a9 Modern type signature style in UniqSet 8bfab43 Efficient checks for stable modules 69d9081 Faster checkFamInstConsistency 0c00097 Udate hsSyn AST to use Trees that Grow