From git at git.haskell.org Sun Jul 2 07:00:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Jul 2017 07:00:16 +0000 (UTC) Subject: [commit: ghc] master: Fix paper link in MVar docs [ci skip] (0592318) Message-ID: <20170702070016.523753A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/05923183fe8478370b58a51398de8c899f954286/ghc >--------------------------------------------------------------- commit 05923183fe8478370b58a51398de8c899f954286 Author: Ömer Sinan Ağacan Date: Sun Jul 2 09:59:57 2017 +0300 Fix paper link in MVar docs [ci skip] >--------------------------------------------------------------- 05923183fe8478370b58a51398de8c899f954286 libraries/base/Control/Concurrent/MVar.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/Control/Concurrent/MVar.hs b/libraries/base/Control/Concurrent/MVar.hs index f76eaeb..393fca8 100644 --- a/libraries/base/Control/Concurrent/MVar.hs +++ b/libraries/base/Control/Concurrent/MVar.hs @@ -25,7 +25,7 @@ -- wait and signal. -- -- They were introduced in the paper --- +-- -- by Simon Peyton Jones, Andrew Gordon and Sigbjorn Finne, though -- some details of their implementation have since then changed (in -- particular, a put on a full 'MVar' used to error, but now merely From git at git.haskell.org Mon Jul 3 10:29:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 10:29:04 +0000 (UTC) Subject: [commit: ghc] master: rename tcInstBinder(s)X to tcInstBinder(s) (544ac0d) Message-ID: <20170703102904.ABBC13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/544ac0d2e8fcd22d1761586436422c2b9396fac7/ghc >--------------------------------------------------------------- commit 544ac0d2e8fcd22d1761586436422c2b9396fac7 Author: Gabor Greif Date: Fri Jun 30 14:49:03 2017 +0200 rename tcInstBinder(s)X to tcInstBinder(s) Summary: Simplify naming scheme of tcInstBinder(s)X Test Plan: Eyeball and compile Reviewers: austin, goldfire, bgamari Subscribers: goldfire, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3690 >--------------------------------------------------------------- 544ac0d2e8fcd22d1761586436422c2b9396fac7 compiler/typecheck/Inst.hs | 16 ++++++++-------- compiler/typecheck/TcHsType.hs | 10 +++++----- compiler/typecheck/TcMType.hs | 2 +- 3 files changed, 14 insertions(+), 14 deletions(-) diff --git a/compiler/typecheck/Inst.hs b/compiler/typecheck/Inst.hs index 093c004..a565959 100644 --- a/compiler/typecheck/Inst.hs +++ b/compiler/typecheck/Inst.hs @@ -15,7 +15,7 @@ module Inst ( instCall, instDFunType, instStupidTheta, newWanted, newWanteds, - tcInstBindersX, tcInstBinderX, + tcInstBinders, tcInstBinder, newOverloadedLit, mkOverLit, @@ -380,19 +380,19 @@ instStupidTheta orig theta -- | This is used to instantiate binders when type-checking *types* only. -- The @VarEnv Kind@ gives some known instantiations. -- See also Note [Bidirectional type checking] -tcInstBindersX :: TCvSubst -> Maybe (VarEnv Kind) +tcInstBinders :: TCvSubst -> Maybe (VarEnv Kind) -> [TyBinder] -> TcM (TCvSubst, [TcType]) -tcInstBindersX subst mb_kind_info bndrs - = do { (subst, args) <- mapAccumLM (tcInstBinderX mb_kind_info) subst bndrs +tcInstBinders subst mb_kind_info bndrs + = do { (subst, args) <- mapAccumLM (tcInstBinder mb_kind_info) subst bndrs ; traceTc "instantiating tybinders:" (vcat $ zipWith (\bndr arg -> ppr bndr <+> text ":=" <+> ppr arg) bndrs args) ; return (subst, args) } -- | Used only in *types* -tcInstBinderX :: Maybe (VarEnv Kind) +tcInstBinder :: Maybe (VarEnv Kind) -> TCvSubst -> TyBinder -> TcM (TCvSubst, TcType) -tcInstBinderX mb_kind_info subst (Named (TvBndr tv _)) +tcInstBinder mb_kind_info subst (Named (TvBndr tv _)) = case lookup_tv tv of Just ki -> return (extendTvSubstAndInScope subst tv ki, ki) Nothing -> do { (subst', tv') <- newMetaTyVarX subst tv @@ -402,7 +402,7 @@ tcInstBinderX mb_kind_info subst (Named (TvBndr tv _)) ; lookupVarEnv env tv } -tcInstBinderX _ subst (Anon ty) +tcInstBinder _ subst (Anon ty) -- This is the *only* constraint currently handled in types. | Just (mk, role, k1, k2) <- get_pred_tys_maybe substed_ty = do { let origin = TypeEqOrigin { uo_actual = k1 @@ -411,7 +411,7 @@ tcInstBinderX _ subst (Anon ty) ; co <- case role of Nominal -> unifyKind noThing k1 k2 Representational -> emitWantedEq origin KindLevel role k1 k2 - Phantom -> pprPanic "tcInstBinderX Phantom" (ppr ty) + Phantom -> pprPanic "tcInstBinder Phantom" (ppr ty) ; arg' <- mk co k1 k2 ; return (subst, arg') } diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 11e4b48..9653685 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -56,7 +56,7 @@ import TcIface import TcSimplify ( solveEqualities ) import TcType import TcHsSyn( zonkSigType ) -import Inst ( tcInstBindersX, tcInstBinderX ) +import Inst ( tcInstBinders, tcInstBinder ) import Type import Kind import RdrName( lookupLocalRdrOcc ) @@ -422,7 +422,7 @@ metavariable. In types, however, we're not so lucky, because *we cannot re-generalize*! There is no lambda. So, we must be careful only to instantiate at the last possible moment, when we're sure we're never going to want the lost polymorphism -again. This is done in calls to tcInstBindersX. +again. This is done in calls to tcInstBinders. To implement this behavior, we use bidirectional type checking, where we explicitly think about whether we know the kind of the type we're checking @@ -810,7 +810,7 @@ tcInferArgs fun tc_binders mb_kind_info args -- now, we need to instantiate any remaining invisible arguments ; let (invis_bndrs, other_binders) = break isVisibleBinder leftover_binders ; (subst', invis_args) - <- tcInstBindersX subst mb_kind_info invis_bndrs + <- tcInstBinders subst mb_kind_info invis_bndrs ; return ( subst' , other_binders , args' `chkAppend` invis_args @@ -838,7 +838,7 @@ tc_infer_args mode orig_ty binders mb_kind_info orig_args n0 go subst (binder:binders) all_args@(arg:args) n acc | isInvisibleBinder binder = do { traceTc "tc_infer_args (invis)" (ppr binder) - ; (subst', arg') <- tcInstBinderX mb_kind_info subst binder + ; (subst', arg') <- tcInstBinder mb_kind_info subst binder ; go subst' binders all_args n (arg' : acc) } | otherwise @@ -932,7 +932,7 @@ instantiateTyN n ty ki empty_subst = mkEmptyTCvSubst (mkInScopeSet (tyCoVarsOfType ki)) in if num_to_inst <= 0 then return (ty, ki) else - do { (subst, inst_args) <- tcInstBindersX empty_subst Nothing inst_bndrs + do { (subst, inst_args) <- tcInstBinders empty_subst Nothing inst_bndrs ; let rebuilt_ki = mkPiTys leftover_bndrs inner_ki ki' = substTy subst rebuilt_ki ; traceTc "instantiateTyN" (vcat [ ppr ty <+> dcolon <+> ppr ki diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index d26b257..0a1de44 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -843,7 +843,7 @@ new_meta_tv_x info subst tv -- is not yet fixed so leaving as unchecked for now. -- OLD NOTE: -- Unchecked because we call newMetaTyVarX from - -- tcInstBinderX, which is called from tc_infer_args + -- tcInstBinder, which is called from tc_infer_args -- which does not yet take enough trouble to ensure -- the in-scope set is right; e.g. Trac #12785 trips -- if we use substTy here From git at git.haskell.org Mon Jul 3 22:05:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 22:05:39 +0000 (UTC) Subject: [commit: packages/array] master: Prepare for 0.5.2.0 release (9a23fea) Message-ID: <20170703220539.C96F93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array On branch : master Link : http://git.haskell.org/packages/array.git/commitdiff/9a23feac0b78e713c0f7877066fa24dbc2217c20 >--------------------------------------------------------------- commit 9a23feac0b78e713c0f7877066fa24dbc2217c20 Author: Herbert Valerio Riedel Date: Tue Jul 4 00:04:30 2017 +0200 Prepare for 0.5.2.0 release >--------------------------------------------------------------- 9a23feac0b78e713c0f7877066fa24dbc2217c20 array.cabal | 2 +- changelog.md | 4 +++- 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/array.cabal b/array.cabal index 58b8cf1..1a71bab 100644 --- a/array.cabal +++ b/array.cabal @@ -1,5 +1,5 @@ name: array -version: 0.5.1.2 +version: 0.5.2.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE diff --git a/changelog.md b/changelog.md index 209f2f0..e537cd0 100644 --- a/changelog.md +++ b/changelog.md @@ -1,9 +1,11 @@ # Changelog for [`array` package](http://hackage.haskell.org/package/array) -## 0.5.1.2 *May 2017* +## 0.5.2.0 *Jul 2017* * Bundled with GHC 8.2.1 * Overflow check in `unsafeNewArray` (#229) + * Fix and simplify handling of `Bool` arrays + * Export `unsafeFreezeIOUArray` from `Data.Array.IO.Internals` * Drop support for GHC versions prior to GHC 7.8 ## 0.5.1.1 *Apr 2016* From git at git.haskell.org Mon Jul 3 22:15:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 22:15:28 +0000 (UTC) Subject: [commit: packages/array] tag 'v0.5.2.0' created Message-ID: <20170703221528.08A893A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array New tag : v0.5.2.0 Referencing: 783e760d086e2cfdbb9a36d7166c2468a2c94ed6 From git at git.haskell.org Mon Jul 3 22:58:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 22:58:37 +0000 (UTC) Subject: [commit: ghc] master: Allow per-argument documentation on pattern synonym signatures (287a405) Message-ID: <20170703225837.4B3733A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/287a40564a7024b55daf0b063683ce889f8a18d9/ghc >--------------------------------------------------------------- commit 287a40564a7024b55daf0b063683ce889f8a18d9 Author: alexbiehl Date: Mon Jul 3 16:53:10 2017 -0400 Allow per-argument documentation on pattern synonym signatures haddock-2.18 supports user defined pattern synonym signatures so this seems like a welcomed addition. Reviewers: austin, bgamari, mpickering Reviewed By: bgamari, mpickering Subscribers: rwbarton, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D3699 >--------------------------------------------------------------- 287a40564a7024b55daf0b063683ce889f8a18d9 compiler/parser/Parser.y | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 603ac27..672b6f7 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -1394,7 +1394,7 @@ where_decls :: { Located ([AddAnn] ,sL1 $3 (snd $ unLoc $3)) } pattern_synonym_sig :: { LSig GhcPs } - : 'pattern' con_list '::' sigtype + : 'pattern' con_list '::' sigtypedoc {% ams (sLL $1 $> $ PatSynSig (unLoc $2) (mkLHsSigType $4)) [mj AnnPattern $1, mu AnnDcolon $3] } From git at git.haskell.org Mon Jul 3 22:58:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 22:58:40 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Wibbles in shared libraries discussion (84d6831a) Message-ID: <20170703225840.0602B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/84d6831ae67ed7a543f7b14f04fc569e924ce1dd/ghc >--------------------------------------------------------------- commit 84d6831ae67ed7a543f7b14f04fc569e924ce1dd Author: Ben Gamari Date: Fri Jun 30 14:10:35 2017 -0400 users-guide: Wibbles in shared libraries discussion >--------------------------------------------------------------- 84d6831ae67ed7a543f7b14f04fc569e924ce1dd docs/users_guide/shared_libs.rst | 21 ++++++++++----------- 1 file changed, 10 insertions(+), 11 deletions(-) diff --git a/docs/users_guide/shared_libs.rst b/docs/users_guide/shared_libs.rst index 1d294b8..c0c54f1 100644 --- a/docs/users_guide/shared_libs.rst +++ b/docs/users_guide/shared_libs.rst @@ -117,12 +117,12 @@ the :ghc-flag:`-dynamic`, :ghc-flag:`-fPIC` and :ghc-flag:`-shared` flags: ghc --make -dynamic -shared -fPIC Foo.hs -o libfoo.so -As before, the ``-dynamic`` flag specifies that this library links -against the shared library versions of the rts and base package. The -``-fPIC`` flag is required for all code that will end up in a shared -library. The ``-shared`` flag specifies to make a shared library rather -than a program. To make this clearer we can break this down into -separate compilation and link steps: +As before, the :ghc-flag:`-dynamic` flag specifies that this library links +against the shared library versions of the ``rts`` and ``base`` package. The +:ghc-flag:`-fPIC` flag is required for all code that will end up in a shared +library. The :ghc-flag:`-shared` flag specifies to make a shared library rather +than a program. To make this clearer we can break this down into separate +compilation and link steps: .. code-block:: none @@ -130,12 +130,11 @@ separate compilation and link steps: ghc -dynamic -shared Foo.o -o libfoo.so In principle you can use :ghc-flag:`-shared` without :ghc-flag:`-dynamic` in the -link step. That means to statically link the rts all the base libraries into -your new shared library. This would make a very big, but standalone -shared library. On most platforms however that would require all the +link step. That means to statically link the runtime system and all of the base +libraries into your new shared library. This would make a very big, but +standalone shared library. On most platforms however that would require all the static libraries to have been built with :ghc-flag:`-fPIC` so that the code is -suitable to include into a shared library and we do not do that at the -moment. +suitable to include into a shared library and we do not do that at the moment. .. warning:: If your shared library exports a Haskell API then you cannot From git at git.haskell.org Mon Jul 3 22:58:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 22:58:43 +0000 (UTC) Subject: [commit: ghc] master: Implement recompilation checking for -fignore-asserts (1a9c3c4) Message-ID: <20170703225843.A8F173A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1a9c3c44ef82803766a8db91a619393c43195ad3/ghc >--------------------------------------------------------------- commit 1a9c3c44ef82803766a8db91a619393c43195ad3 Author: Ömer Sinan Ağacan Date: Mon Jul 3 16:53:31 2017 -0400 Implement recompilation checking for -fignore-asserts Test Plan: Added a test which was previously failing Reviewers: austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #13914 Differential Revision: https://phabricator.haskell.org/D3698 >--------------------------------------------------------------- 1a9c3c44ef82803766a8db91a619393c43195ad3 compiler/iface/FlagChecker.hs | 6 +++++- testsuite/tests/driver/T13914/Makefile | 16 ++++++++++++++++ testsuite/tests/driver/T13914/T13914.stdout | 16 ++++++++++++++++ testsuite/tests/driver/T13914/all.T | 4 ++++ testsuite/tests/driver/T13914/main.hs | 3 +++ 5 files changed, 44 insertions(+), 1 deletion(-) diff --git a/compiler/iface/FlagChecker.hs b/compiler/iface/FlagChecker.hs index 2c0b6c4..fd0459d 100644 --- a/compiler/iface/FlagChecker.hs +++ b/compiler/iface/FlagChecker.hs @@ -61,8 +61,12 @@ fingerprintDynFlags dflags at DynFlags{..} this_mod nameio = -- hpcDir is output-only, so we should recompile if it changes hpc = if gopt Opt_Hpc dflags then Just hpcDir else Nothing + -- -fignore-asserts, which affects how `Control.Exception.assert` works + ignore_asserts = gopt Opt_IgnoreAsserts dflags + -- Nesting just to avoid ever more Binary tuple instances - flags = (mainis, safeHs, lang, cpp, paths, (prof, opt, hpc)) + flags = (mainis, safeHs, lang, cpp, paths, + (prof, opt, hpc, ignore_asserts)) in -- pprTrace "flags" (ppr flags) $ computeFingerprint nameio flags diff --git a/testsuite/tests/driver/T13914/Makefile b/testsuite/tests/driver/T13914/Makefile new file mode 100644 index 0000000..764942c --- /dev/null +++ b/testsuite/tests/driver/T13914/Makefile @@ -0,0 +1,16 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +t13914: + echo "Without -fignore-asserts" + '$(TEST_HC)' $(TEST_HC_OPTS) main.hs + (./main 2>&1); true + sleep 1 + echo "With -fignore-asserts" + '$(TEST_HC)' $(TEST_HC_OPTS) -fignore-asserts main.hs + ./main 2>&1 + sleep 1 + echo "Without -fignore-asserts" + '$(TEST_HC)' $(TEST_HC_OPTS) main.hs + (./main 2>&1); true diff --git a/testsuite/tests/driver/T13914/T13914.stdout b/testsuite/tests/driver/T13914/T13914.stdout new file mode 100644 index 0000000..04d14aa --- /dev/null +++ b/testsuite/tests/driver/T13914/T13914.stdout @@ -0,0 +1,16 @@ +Without -fignore-asserts +[1 of 1] Compiling Main ( main.hs, main.o ) +Linking main ... +main: Assertion failed +CallStack (from HasCallStack): + assert, called at main.hs:3:8 in main:Main +With -fignore-asserts +[1 of 1] Compiling Main ( main.hs, main.o ) [flags changed] +Linking main ... +OK +Without -fignore-asserts +[1 of 1] Compiling Main ( main.hs, main.o ) [flags changed] +Linking main ... +main: Assertion failed +CallStack (from HasCallStack): + assert, called at main.hs:3:8 in main:Main diff --git a/testsuite/tests/driver/T13914/all.T b/testsuite/tests/driver/T13914/all.T new file mode 100644 index 0000000..2e6a952 --- /dev/null +++ b/testsuite/tests/driver/T13914/all.T @@ -0,0 +1,4 @@ +test('T13914', + [extra_files(['main.hs'])], + run_command, + ['$MAKE -s --no-print-directory t13914']) diff --git a/testsuite/tests/driver/T13914/main.hs b/testsuite/tests/driver/T13914/main.hs new file mode 100644 index 0000000..859f3e6 --- /dev/null +++ b/testsuite/tests/driver/T13914/main.hs @@ -0,0 +1,3 @@ +import Control.Exception (assert) + +main = assert False (putStrLn "OK") From git at git.haskell.org Mon Jul 3 22:58:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 22:58:47 +0000 (UTC) Subject: [commit: ghc] master: Fix -fno-code for modules that use -XQuasiQuotes (d55bea1) Message-ID: <20170703225847.175EB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d55bea14c745f7f448fb24673a21b511d1c1c222/ghc >--------------------------------------------------------------- commit d55bea14c745f7f448fb24673a21b511d1c1c222 Author: Douglas Wilson Date: Mon Jul 3 16:54:29 2017 -0400 Fix -fno-code for modules that use -XQuasiQuotes In commit 53c78be0aab76a3107c4dacbb1d177afacdd37fa object code is generated for modules depended on by modules that use -XTemplateHaskell. This turns the same logic on for modules that use -XQuasiQuotes. A test is added. Note that I've based this of D3646, as it has a function I want to use. Test Plan: ./validate Reviewers: austin, bgamari, alexbiehl Reviewed By: alexbiehl Subscribers: alexbiehl, rwbarton, thomie GHC Trac Issues: #13863 Differential Revision: https://phabricator.haskell.org/D3677 >--------------------------------------------------------------- d55bea14c745f7f448fb24673a21b511d1c1c222 compiler/main/GHC.hs | 11 +---------- compiler/main/GhcMake.hs | 2 +- compiler/main/HscTypes.hs | 18 ++++++++++++++++++ testsuite/tests/quasiquotation/T13863/A.hs | 8 ++++++++ testsuite/tests/quasiquotation/T13863/B.hs | 7 +++++++ testsuite/tests/quasiquotation/T13863/all.T | 1 + 6 files changed, 36 insertions(+), 11 deletions(-) diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index 2102009..4a45bea 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -23,7 +23,7 @@ module GHC ( gcatch, gbracket, gfinally, printException, handleSourceError, - needsTemplateHaskell, + needsTemplateHaskellOrQQ, -- * Flags and settings DynFlags(..), GeneralFlag(..), Severity(..), HscTarget(..), gopt, @@ -1075,15 +1075,6 @@ compileCore simplify fn = do getModuleGraph :: GhcMonad m => m ModuleGraph -- ToDo: DiGraph ModSummary getModuleGraph = liftM hsc_mod_graph getSession --- | Determines whether a set of modules requires Template Haskell. --- --- Note that if the session's 'DynFlags' enabled Template Haskell when --- 'depanal' was called, then each module in the returned module graph will --- have Template Haskell enabled whether it is actually needed or not. -needsTemplateHaskell :: ModuleGraph -> Bool -needsTemplateHaskell ms = - any (xopt LangExt.TemplateHaskell . ms_hspp_opts) ms - -- | Return @True@ <==> module is loaded. isLoaded :: GhcMonad m => ModuleName -> m Bool isLoaded m = withSession $ \hsc_env -> diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs index 134a060..5935a77 100644 --- a/compiler/main/GhcMake.hs +++ b/compiler/main/GhcMake.hs @@ -1994,7 +1994,7 @@ enableCodeGenForTH target nodemap = [ ms | mss <- Map.elems nodemap , Right ms <- mss - , xopt LangExt.TemplateHaskell (ms_hspp_opts ms) + , needsTemplateHaskellOrQQ $ [ms] ] transitive_deps_set marked_mods modSums = foldl' go marked_mods modSums go marked_mods ms diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs index fa9c18a..9f1da3f 100644 --- a/compiler/main/HscTypes.hs +++ b/compiler/main/HscTypes.hs @@ -12,6 +12,7 @@ module HscTypes ( HscEnv(..), hscEPS, FinderCache, FindResult(..), InstalledFindResult(..), Target(..), TargetId(..), pprTarget, pprTargetId, + needsTemplateHaskellOrQQ, ModuleGraph, emptyMG, mapMG, HscStatus(..), IServ(..), @@ -199,6 +200,7 @@ import Platform import Util import UniqDSet import GHC.Serialized ( Serialized ) +import qualified GHC.LanguageExtensions as LangExt import Foreign import Control.Monad ( guard, liftM, ap ) @@ -2608,12 +2610,28 @@ soExt platform -- 'GHC.topSortModuleGraph' and 'Digraph.flattenSCC' to achieve this. type ModuleGraph = [ModSummary] + +-- | Determines whether a set of modules requires Template Haskell or +-- Quasi Quotes +-- +-- Note that if the session's 'DynFlags' enabled Template Haskell when +-- 'depanal' was called, then each module in the returned module graph will +-- have Template Haskell enabled whether it is actually needed or not. +needsTemplateHaskellOrQQ :: ModuleGraph -> Bool +needsTemplateHaskellOrQQ mg = any isTemplateHaskellOrQQNonBoot mg + emptyMG :: ModuleGraph emptyMG = [] mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph mapMG = map +isTemplateHaskellOrQQNonBoot :: ModSummary -> Bool +isTemplateHaskellOrQQNonBoot ms = + (xopt LangExt.TemplateHaskell (ms_hspp_opts ms) + || xopt LangExt.QuasiQuotes (ms_hspp_opts ms)) && + not (isBootSummary ms) + -- | A single node in a 'ModuleGraph'. The nodes of the module graph -- are one of: -- diff --git a/testsuite/tests/quasiquotation/T13863/A.hs b/testsuite/tests/quasiquotation/T13863/A.hs new file mode 100644 index 0000000..0d3137c --- /dev/null +++ b/testsuite/tests/quasiquotation/T13863/A.hs @@ -0,0 +1,8 @@ +{-# OPTIONS_GHC -Wno-missing-fields#-} +module A where + +import Language.Haskell.TH +import Language.Haskell.TH.Quote + +aquoter :: QuasiQuoter +aquoter = QuasiQuoter {quoteType = conT . mkName } diff --git a/testsuite/tests/quasiquotation/T13863/B.hs b/testsuite/tests/quasiquotation/T13863/B.hs new file mode 100644 index 0000000..649a551 --- /dev/null +++ b/testsuite/tests/quasiquotation/T13863/B.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE QuasiQuotes #-} +module B where + +import A + +foo:: [aquoter|Int|] -> [aquoter|String|] +foo = show diff --git a/testsuite/tests/quasiquotation/T13863/all.T b/testsuite/tests/quasiquotation/T13863/all.T new file mode 100644 index 0000000..c29dc20 --- /dev/null +++ b/testsuite/tests/quasiquotation/T13863/all.T @@ -0,0 +1 @@ +test('T13863', [req_interp, omit_ways(prof_ways), extra_files(['A.hs', 'B.hs'])], multimod_compile, ['B', '-fno-code -v0']) \ No newline at end of file From git at git.haskell.org Mon Jul 3 22:58:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 22:58:49 +0000 (UTC) Subject: [commit: ghc] master: CmmParse: Emit source notes for assignments (0c1f905) Message-ID: <20170703225849.E41D73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0c1f905aea4d5a9e2e329ba6b57d5a009635ce3d/ghc >--------------------------------------------------------------- commit 0c1f905aea4d5a9e2e329ba6b57d5a009635ce3d Author: Ben Gamari Date: Mon Jul 3 17:15:23 2017 -0400 CmmParse: Emit source notes for assignments Currently the line information for bare source C-- is rather spartan. These add notes for assignments, which tend to be useful to identify. Unfortunately, we had to settle for approximate source locations as none of the parsers in CmmParse return located things. However, I don't think it's worth changing this. >--------------------------------------------------------------- 0c1f905aea4d5a9e2e329ba6b57d5a009635ce3d compiler/cmm/CmmParse.y | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 9d404aa..e2fe593 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -593,9 +593,9 @@ stmt :: { CmmParse () } | lreg '=' expr ';' - { do reg <- $1; e <- $3; emitAssign reg e } + { do reg <- $1; e <- $3; withSourceNote $2 $4 (emitAssign reg e) } | type '[' expr ']' '=' expr ';' - { doStore $1 $3 $6 } + { withSourceNote $2 $7 (doStore $1 $3 $6) } -- Gah! We really want to say "foreign_results" but that causes -- a shift/reduce conflict with assignment. We either From git at git.haskell.org Mon Jul 3 22:58:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 22:58:52 +0000 (UTC) Subject: [commit: ghc] master: Bump array submodule to v0.5.2.0 (5aee331) Message-ID: <20170703225852.A17853A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5aee331152c251525bc73b792660851dc5dddc29/ghc >--------------------------------------------------------------- commit 5aee331152c251525bc73b792660851dc5dddc29 Author: Ben Gamari Date: Mon Jul 3 18:22:38 2017 -0400 Bump array submodule to v0.5.2.0 >--------------------------------------------------------------- 5aee331152c251525bc73b792660851dc5dddc29 libraries/array | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/array b/libraries/array index f7b69e9..9a23fea 160000 --- a/libraries/array +++ b/libraries/array @@ -1 +1 @@ -Subproject commit f7b69e9cb914cb69bbede5264729523fb8669db1 +Subproject commit 9a23feac0b78e713c0f7877066fa24dbc2217c20 From git at git.haskell.org Mon Jul 3 22:58:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 22:58:55 +0000 (UTC) Subject: [commit: ghc] master: Tag the FUN before making a PAP (#13767) (f9c6d53) Message-ID: <20170703225855.646483A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f9c6d53fe997f1c560cda6f346f4b201711df37c/ghc >--------------------------------------------------------------- commit f9c6d53fe997f1c560cda6f346f4b201711df37c Author: Simon Marlow Date: Mon Jul 3 16:54:00 2017 -0400 Tag the FUN before making a PAP (#13767) Pointers to FUNs are not guaranteed to be tagged in general, because the compiler doesn't always know the arity of a FUN when it needs to reference it, e.g. with -O0 when the function is in another module. However, there's one case where we can put the correct tag on a FUN: when it is referenced by a PAP, because when building the PAP we know the arity and we can tag the pointer correctly. The AutoApply code does this, and the sanity checker checks it, but the interpreter did not respect this invariant. This patch fixes it. Test Plan: ``` (cd ghc && make 2 GhcDebugged=YES) ./inplace/bin/ghc-stage2 --interpreter +RTS -DS ``` Reviewers: niteria, bgamari, austin, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13767 Differential Revision: https://phabricator.haskell.org/D3680 >--------------------------------------------------------------- f9c6d53fe997f1c560cda6f346f4b201711df37c rts/Interpreter.c | 14 ++++++++++++-- 1 file changed, 12 insertions(+), 2 deletions(-) diff --git a/rts/Interpreter.c b/rts/Interpreter.c index 9291473..a2f0b58 100644 --- a/rts/Interpreter.c +++ b/rts/Interpreter.c @@ -406,8 +406,18 @@ eval_obj: case FUN_STATIC: #if defined(PROFILING) if (cap->r.rCCCS != obj->header.prof.ccs) { + int arity = get_fun_itbl(obj)->f.arity; + // Tag the function correctly. We guarantee that pap->fun + // is correctly tagged (this is checked by + // Sanity.c:checkPAP()), but we don't guarantee that every + // pointer to a FUN is tagged on the stack or elsewhere, + // so we fix the tag here. (#13767) + // For full details of the invariants on tagging, see + // https://ghc.haskell.org/trac/ghc/wiki/Commentary/Rts/HaskellExecution/PointerTagging tagged_obj = - newEmptyPAP(cap, tagged_obj, get_fun_itbl(obj)->f.arity); + newEmptyPAP(cap, + arity <= TAG_MASK ? obj + arity : obj, + arity); } #endif break; @@ -424,7 +434,7 @@ eval_obj: ASSERT(((StgBCO *)obj)->arity > 0); #if defined(PROFILING) if (cap->r.rCCCS != obj->header.prof.ccs) { - tagged_obj = newEmptyPAP(cap, tagged_obj, ((StgBCO *)obj)->arity); + tagged_obj = newEmptyPAP(cap, obj, ((StgBCO *)obj)->arity); } #endif break; From git at git.haskell.org Mon Jul 3 22:58:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 22:58:58 +0000 (UTC) Subject: [commit: ghc] master: Fix #13311 by using tcSplitNestedSigmaTys in the right place (c3a7862) Message-ID: <20170703225858.E4B543A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c3a78623cf7bb74c8ca0749f1216e802aa37a721/ghc >--------------------------------------------------------------- commit c3a78623cf7bb74c8ca0749f1216e802aa37a721 Author: Ryan Scott Date: Mon Jul 3 16:54:14 2017 -0400 Fix #13311 by using tcSplitNestedSigmaTys in the right place Previously, we we only using `tcSplitSigmaTy` when determining if a function had been applied to too few arguments, so it wouldn't work for functions with nested `forall`s. Thankfully, this is easily fixed with a dash of `tcSplitNestedSigmaTys`. Test Plan: make test TEST=T13311 Reviewers: austin, bgamari, simonpj Reviewed By: bgamari Subscribers: goldfire, simonpj, rwbarton, thomie GHC Trac Issues: #13311 Differential Revision: https://phabricator.haskell.org/D3678 >--------------------------------------------------------------- c3a78623cf7bb74c8ca0749f1216e802aa37a721 compiler/typecheck/TcExpr.hs | 44 +++++++++++++++++++++- compiler/typecheck/TcTyClsDecls.hs | 11 +++--- testsuite/tests/typecheck/should_fail/T13311.hs | 10 +++++ .../tests/typecheck/should_fail/T13311.stderr | 12 ++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 5 files changed, 72 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs index 960d181..cf8bf0c 100644 --- a/compiler/typecheck/TcExpr.hs +++ b/compiler/typecheck/TcExpr.hs @@ -2413,7 +2413,11 @@ addFunResCtxt has_args fun fun_res_ty env_ty do { dumping <- doptM Opt_D_dump_tc_trace ; MASSERT( dumping ) ; newFlexiTyVarTy liftedTypeKind } - ; let (_, _, fun_tau) = tcSplitSigmaTy fun_res' + ; let -- See Note [Splitting nested sigma types in mismatched + -- function types] + (_, _, fun_tau) = tcSplitNestedSigmaTys fun_res' + -- No need to call tcSplitNestedSigmaTys here, since env_ty is + -- an ExpRhoTy, i.e., it's already deeply instantiated. (_, _, env_tau) = tcSplitSigmaTy env' (args_fun, res_fun) = tcSplitFunTys fun_tau (args_env, res_env) = tcSplitFunTys env_tau @@ -2440,6 +2444,44 @@ addFunResCtxt has_args fun fun_res_ty env_ty Just (tc, _) -> isAlgTyCon tc Nothing -> False +{- +Note [Splitting nested sigma types in mismatched function types] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +When one applies a function to too few arguments, GHC tries to determine this +fact if possible so that it may give a helpful error message. It accomplishes +this by checking if the type of the applied function has more argument types +than supplied arguments. + +Previously, GHC computed the number of argument types through tcSplitSigmaTy. +This is incorrect in the face of nested foralls, however! This caused Trac +#13311, for instance: + + f :: forall a. (Monoid a) => forall b. (Monoid b) => Maybe a -> Maybe b + +If one uses `f` like so: + + do { f; putChar 'a' } + +Then tcSplitSigmaTy will decompose the type of `f` into: + + Tyvars: [a] + Context: (Monoid a) + Argument types: [] + Return type: forall b. Monoid b => Maybe a -> Maybe b + +That is, it will conclude that there are *no* argument types, and since `f` +was given no arguments, it won't print a helpful error message. On the other +hand, tcSplitNestedSigmaTys correctly decomposes `f`'s type down to: + + Tyvars: [a, b] + Context: (Monoid a, Monoid b) + Argument types: [Maybe a] + Return type: Maybe b + +So now GHC recognizes that `f` has one more argument type than it was actually +provided. +-} + badFieldTypes :: [(FieldLabelString,TcType)] -> SDoc badFieldTypes prs = hang (text "Record update for insufficiently polymorphic field" diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index d253dc3..7400483 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -2498,7 +2498,7 @@ checkValidClass cls op_name = idName sel_id op_ty = idType sel_id (_,cls_pred,tau1) = tcSplitMethodTy op_ty - -- See Note [Splitting nested sigma types] + -- See Note [Splitting nested sigma types in class type signatures] (_,op_theta,tau2) = tcSplitNestedSigmaTys tau1 check_constraint :: TcPredType -> TcM () @@ -2550,7 +2550,8 @@ checkValidClass cls -- Note [Default method type signatures must align] -- to learn why this is OK. -- - -- See also Note [Splitting nested sigma types] + -- See also + -- Note [Splitting nested sigma types in class type signatures] -- for an explanation of why we don't use tcSplitSigmaTy here. (_, _, dm_tau) = tcSplitNestedSigmaTys dm_ty @@ -2715,10 +2716,10 @@ when we validity-check default type signatures, we ignore contexts completely. Note that when checking whether two type signatures match, we must take care to split as many foralls as it takes to retrieve the tau types we which to check. -See Note [Splitting nested sigma types]. +See Note [Splitting nested sigma types in class type signatures]. -Note [Splitting nested sigma types] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Note [Splitting nested sigma types in class type signatures] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider this type synonym and class definition: type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t diff --git a/testsuite/tests/typecheck/should_fail/T13311.hs b/testsuite/tests/typecheck/should_fail/T13311.hs new file mode 100644 index 0000000..811d6fe --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T13311.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE RankNTypes #-} +module T13311 where + +f :: forall a. (Monoid a) => forall b. (Monoid b) => Maybe a -> Maybe b +f _ = mempty + +g :: IO () +g = do + f + putChar 'a' diff --git a/testsuite/tests/typecheck/should_fail/T13311.stderr b/testsuite/tests/typecheck/should_fail/T13311.stderr new file mode 100644 index 0000000..923f378 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T13311.stderr @@ -0,0 +1,12 @@ + +T13311.hs:9:3: error: + • Couldn't match expected type ‘IO a1’ + with actual type ‘Maybe a0 -> Maybe b0’ + • Probable cause: ‘f’ is applied to too few arguments + In a stmt of a 'do' block: f + In the expression: + do f + putChar 'a' + In an equation for ‘g’: + g = do f + putChar 'a' diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 5cc8171..2ac572f 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -435,6 +435,7 @@ test('LevPolyBounded', normal, compile_fail, ['']) test('T13487', normal, compile, ['']) test('T13292', normal, multimod_compile, ['T13292', '-v0 -fdefer-type-errors']) test('T13300', normal, compile_fail, ['']) +test('T13311', normal, compile_fail, ['']) test('T12709', normal, compile_fail, ['']) test('T13446', normal, compile_fail, ['']) test('T13506', normal, compile_fail, ['']) From git at git.haskell.org Mon Jul 3 23:42:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 23:42:51 +0000 (UTC) Subject: [commit: ghc] master: rts: Fix uninitialised variable uses (8f8d756) Message-ID: <20170703234251.61B683A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8f8d756c5a29217ff79154caa1696b6e572d186f/ghc >--------------------------------------------------------------- commit 8f8d756c5a29217ff79154caa1696b6e572d186f Author: Ben Gamari Date: Mon Jul 3 19:07:59 2017 -0400 rts: Fix uninitialised variable uses Strangely gcc 5.4 compiling on amd64 (nixos) complained about these. Both warnings look correct, so I'm not sure why we haven't been seeing these up until now. Test Plan: Validate Reviewers: simonmar, austin, erikd Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3693 >--------------------------------------------------------------- 8f8d756c5a29217ff79154caa1696b6e572d186f rts/Interpreter.c | 2 +- rts/sm/MarkWeak.c | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/rts/Interpreter.c b/rts/Interpreter.c index a2f0b58..a22e966 100644 --- a/rts/Interpreter.c +++ b/rts/Interpreter.c @@ -285,7 +285,7 @@ interpretBCO (Capability* cap) // that these entities are non-aliasable. register StgPtr Sp; // local state -- stack pointer register StgPtr SpLim; // local state -- stack lim pointer - register StgClosure *tagged_obj = 0, *obj; + register StgClosure *tagged_obj = 0, *obj = NULL; uint32_t n, m; LOAD_THREAD_STATE(); diff --git a/rts/sm/MarkWeak.c b/rts/sm/MarkWeak.c index 691e56a..9a077b3d14 100644 --- a/rts/sm/MarkWeak.c +++ b/rts/sm/MarkWeak.c @@ -364,7 +364,7 @@ static void tidyThreadList (generation *gen) static void checkWeakPtrSanity(StgWeak *hd, StgWeak *tl) { StgWeak *w, *prev; - for (w = hd; w != NULL; prev = w, w = w->link) { + for (prev = NULL, w = hd; w != NULL; prev = w, w = w->link) { ASSERT(INFO_PTR_TO_STRUCT(UNTAG_CLOSURE((StgClosure*)w)->header.info)->type == WEAK || UNTAG_CLOSURE((StgClosure*)w)->header.info == &stg_DEAD_WEAK_info); checkClosure((StgClosure*)w); From git at git.haskell.org Mon Jul 3 23:42:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 23:42:54 +0000 (UTC) Subject: [commit: ghc] master: ApplicativeDo: document behaviour with strict patterns (#13875) (af403b2) Message-ID: <20170703234254.E9D723A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/af403b2eb50abde6a7992470032d7df5faea043e/ghc >--------------------------------------------------------------- commit af403b2eb50abde6a7992470032d7df5faea043e Author: Simon Marlow Date: Mon Jul 3 19:08:30 2017 -0400 ApplicativeDo: document behaviour with strict patterns (#13875) Test Plan: unit tests, built docs Reviewers: dfeuer, bgamari, simonpj, austin, erikd Subscribers: rwbarton, thomie GHC Trac Issues: #13875, #13242 Differential Revision: https://phabricator.haskell.org/D3691 >--------------------------------------------------------------- af403b2eb50abde6a7992470032d7df5faea043e docs/users_guide/glasgow_exts.rst | 49 ++++++++++++++++++++++++++++++++++---- testsuite/tests/ado/T13242.hs | 2 +- testsuite/tests/ado/T13242a.hs | 13 ++++++++++ testsuite/tests/ado/T13242a.stderr | 47 ++++++++++++++++++++++++++++++++++++ testsuite/tests/ado/all.T | 1 + 5 files changed, 107 insertions(+), 5 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index d473841..c3a2d69 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -928,6 +928,7 @@ is as follows. If the do-expression has the following form: :: do p1 <- E1; ...; pn <- En; return E where none of the variables defined by ``p1...pn`` are mentioned in ``E1...En``, +and ``p1...pn`` are all variables or lazy patterns, then the expression will only require ``Applicative``. Otherwise, the expression will require ``Monad``. The block may return a pure expression ``E`` depending upon the results ``p1...pn`` with either ``return`` or ``pure``. @@ -967,12 +968,47 @@ the optimal solution, provided as an option: statements). The default ``ApplicativeDo`` algorithm is ``O(n^2)``. +.. _applicative-do-strict: + +Strict patterns +~~~~~~~~~~~~~~~ + + +A strict pattern match in a bind statement prevents +``ApplicativeDo`` from transforming that statement to use +``Applicative``. This is because the transformation would change the +semantics by making the expression lazier. + +For example, this code will require a ``Monad`` constraint:: + + > :t \m -> do { (x:xs) <- m; return x } + \m -> do { (x:xs) <- m; return x } :: Monad m => m [b] -> m b + +but making the pattern match lazy allows it to have a ``Functor`` constraint:: + + > :t \m -> do { ~(x:xs) <- m; return x } + \m -> do { ~(x:xs) <- m; return x } :: Functor f => f [b] -> f b + +A "strict pattern match" is any pattern match that can fail. For +example, ``()``, ``(x:xs)``, ``!z``, and ``C x`` are strict patterns, +but ``x`` and ``~(1,2)`` are not. For the purposes of +``ApplicativeDo``, a pattern match against a ``newtype`` constructor +is considered strict. + +When there's a strict pattern match in a sequence of statements, +``ApplicativeDo`` places a ``>>=`` between that statement and the one +that follows it. The sequence may be transformed to use ``<*>`` +elsewhere, but the strict pattern match and the following statement +will always be connected with ``>>=``, to retain the same strictness +semantics as the standard do-notation. If you don't want this, simply +put a ``~`` on the pattern match to make it lazy. + .. _applicative-do-existential: Existential patterns and GADTs ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Note that when the pattern in a statement matches a constructor with +When the pattern in a statement matches a constructor with existential type variables and/or constraints, the transformation that ``ApplicativeDo`` performs may mean that the pattern does not scope over the statements that follow it. This is because the rearrangement @@ -985,7 +1021,8 @@ program does not typecheck:: test = do A x <- undefined - _ <- return True + _ <- return 'a' + _ <- return 'b' return (x == x) The reason is that the ``Eq`` constraint that would be brought into @@ -995,8 +1032,12 @@ rearranged the expression to look like this:: test = (\x _ -> x == x) - <$> do A x <- undefined; return x - <*> return True + <$> do A x <- undefined; _ <- return 'a'; return x + <*> return 'b' + +(Note that the ``return 'a'`` and ``return 'b'`` statements are needed +to make ``ApplicativeDo`` apply despite the restriction noted in +:ref:`applicative-do-strict`, because ``A x`` is a strict pattern match.) Turning off ``ApplicativeDo`` lets the program typecheck. This is something to bear in mind when using ``ApplicativeDo`` in combination diff --git a/testsuite/tests/ado/T13242.hs b/testsuite/tests/ado/T13242.hs index ccaa93c..2111b85 100644 --- a/testsuite/tests/ado/T13242.hs +++ b/testsuite/tests/ado/T13242.hs @@ -1,6 +1,6 @@ --- Panic.hs {-# LANGUAGE ApplicativeDo #-} {-# LANGUAGE ExistentialQuantification #-} +{-# LANGUAGE GADTs #-} module T13242 where import Data.STRef diff --git a/testsuite/tests/ado/T13242a.hs b/testsuite/tests/ado/T13242a.hs new file mode 100644 index 0000000..540b041 --- /dev/null +++ b/testsuite/tests/ado/T13242a.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE ApplicativeDo #-} +{-# LANGUAGE ExistentialQuantification #-} +{-# LANGUAGE GADTs #-} +module T13242a where + +data T where A :: forall a . Eq a => a -> T + +test :: IO Bool +test = do + A x <- undefined + _ <- return 'a' + _ <- return 'b' + return (x == x) diff --git a/testsuite/tests/ado/T13242a.stderr b/testsuite/tests/ado/T13242a.stderr new file mode 100644 index 0000000..dc4564f --- /dev/null +++ b/testsuite/tests/ado/T13242a.stderr @@ -0,0 +1,47 @@ + +T13242a.hs:10:5: error: + • Couldn't match expected type ‘a0’ with actual type ‘a’ + because type variable ‘a’ would escape its scope + This (rigid, skolem) type variable is bound by + a pattern with constructor: A :: forall a. Eq a => a -> T, + in a pattern binding in + 'do' block + at T13242a.hs:10:3-5 + • In the expression: + do A x <- undefined + _ <- return 'a' + _ <- return 'b' + return (x == x) + In an equation for ‘test’: + test + = do A x <- undefined + _ <- return 'a' + _ <- return 'b' + return (x == x) + • Relevant bindings include x :: a (bound at T13242a.hs:10:5) + +T13242a.hs:13:11: error: + • Ambiguous type variable ‘a0’ arising from a use of ‘==’ + prevents the constraint ‘(Eq a0)’ from being solved. + Relevant bindings include x :: a0 (bound at T13242a.hs:10:5) + Probable fix: use a type annotation to specify what ‘a0’ should be. + These potential instances exist: + instance Eq Ordering -- Defined in ‘GHC.Classes’ + instance Eq Integer + -- Defined in ‘integer-gmp-1.0.0.1:GHC.Integer.Type’ + instance Eq a => Eq (Maybe a) -- Defined in ‘GHC.Base’ + ...plus 22 others + ...plus five instances involving out-of-scope types + (use -fprint-potential-instances to see them all) + • In a stmt of a 'do' block: return (x == x) + In the expression: + do A x <- undefined + _ <- return 'a' + _ <- return 'b' + return (x == x) + In an equation for ‘test’: + test + = do A x <- undefined + _ <- return 'a' + _ <- return 'b' + return (x == x) diff --git a/testsuite/tests/ado/all.T b/testsuite/tests/ado/all.T index a738c7a..bb1cc16 100644 --- a/testsuite/tests/ado/all.T +++ b/testsuite/tests/ado/all.T @@ -9,4 +9,5 @@ test('T11607', normal, compile_and_run, ['']) test('ado-optimal', normal, compile_and_run, ['']) test('T12490', normal, compile, ['']) test('T13242', normal, compile, ['']) +test('T13242a', normal, compile_fail, ['']) test('T13875', normal, compile_and_run, ['']) From git at git.haskell.org Mon Jul 3 23:42:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 23:42:57 +0000 (UTC) Subject: [commit: ghc] master: configure: Remove --with-curses-includes flag (ef63ff2) Message-ID: <20170703234257.AB23A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ef63ff27251a20ff11e58c9303677fa31e609a88/ghc >--------------------------------------------------------------- commit ef63ff27251a20ff11e58c9303677fa31e609a88 Author: Ben Gamari Date: Mon Jul 3 19:08:43 2017 -0400 configure: Remove --with-curses-includes flag terminfo no longer needs to be able to find the ncurses headers. See https://github.com/judah/terminfo/pull/22. Reviewers: austin, hvr Subscribers: rwbarton, thomie, erikd Differential Revision: https://phabricator.haskell.org/D3688 >--------------------------------------------------------------- ef63ff27251a20ff11e58c9303677fa31e609a88 aclocal.m4 | 5 ----- mk/config.mk.in | 1 - rules/build-package-data.mk | 4 ---- 3 files changed, 10 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 677c0e7..001f813 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -1740,11 +1740,6 @@ AC_DEFUN([FP_CURSES], dnl * Deal with arguments telling us curses is somewhere odd dnl-------------------------------------------------------------------- - AC_ARG_WITH([curses-includes], - [AC_HELP_STRING([--with-curses-includes], - [directory containing curses headers])], - [CURSES_INCLUDE_DIRS=$withval]) - AC_ARG_WITH([curses-libraries], [AC_HELP_STRING([--with-curses-libraries], [directory containing curses libraries])], diff --git a/mk/config.mk.in b/mk/config.mk.in index 189439e..2c62e90 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -890,7 +890,6 @@ ICONV_LIB_DIRS = @ICONV_LIB_DIRS@ GMP_INCLUDE_DIRS = @GMP_INCLUDE_DIRS@ GMP_LIB_DIRS = @GMP_LIB_DIRS@ -CURSES_INCLUDE_DIRS = @CURSES_INCLUDE_DIRS@ CURSES_LIB_DIRS = @CURSES_LIB_DIRS@ # See Note [Disable -O2 in unregisterised mode] diff --git a/rules/build-package-data.mk b/rules/build-package-data.mk index a20afbc..04364b7 100644 --- a/rules/build-package-data.mk +++ b/rules/build-package-data.mk @@ -90,10 +90,6 @@ ifneq "$$(GMP_LIB_DIRS)" "" $1_$2_CONFIGURE_OPTS += --configure-option=--with-gmp-libraries="$$(GMP_LIB_DIRS)" endif -ifneq "$$(CURSES_INCLUDE_DIRS)" "" -$1_$2_CONFIGURE_OPTS += --configure-option=--with-curses-includes="$$(CURSES_INCLUDE_DIRS)" -endif - ifneq "$$(CURSES_LIB_DIRS)" "" $1_$2_CONFIGURE_OPTS += --configure-option=--with-curses-libraries="$$(CURSES_LIB_DIRS)" endif From git at git.haskell.org Mon Jul 3 23:43:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 23:43:00 +0000 (UTC) Subject: [commit: ghc] master: Add -fuse-ld flag to CFLAGS during configure (960918b) Message-ID: <20170703234300.785153A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/960918bd1f7e3811845a525ba85bbd390ddf28c8/ghc >--------------------------------------------------------------- commit 960918bd1f7e3811845a525ba85bbd390ddf28c8 Author: Ben Gamari Date: Mon Jul 3 19:09:39 2017 -0400 Add -fuse-ld flag to CFLAGS during configure The decisions made by configure later in the script may depend upon the linker used. Consequently, it is important that configure uses the same linker as GHC will eventually use. For instance, on Nix I found that a program requiring `libpthread` would link fine with only `-lrt` when linked with BFD ld. However, with gold we needed to explicitly provide the `-lpthread` dependency. Presumably the former would happily loaded any `NEEDED` libraries whereas the latter wants them explicitly given. Regardless, since `configure`'s `NEED_PTHREAD_LIB` check didn't use the `-fuse-ld` flag that GHC would eventually use, we inferred the wrong value, resulting in link errors later in the build. Test Plan: Validate Reviewers: austin, hvr Subscribers: rwbarton, thomie, erikd GHC Trac Issues: #13541 Differential Revision: https://phabricator.haskell.org/D3694 >--------------------------------------------------------------- 960918bd1f7e3811845a525ba85bbd390ddf28c8 configure.ac | 1 + distrib/configure.ac.in | 1 + 2 files changed, 2 insertions(+) diff --git a/configure.ac b/configure.ac index 92d3714..c31deba 100644 --- a/configure.ac +++ b/configure.ac @@ -535,6 +535,7 @@ FIND_LD([$target],[GccUseLdOpt]) CONF_GCC_LINKER_OPTS_STAGE1="$CONF_GCC_LINKER_OPTS_STAGE1 $GccUseLdOpt" CONF_GCC_LINKER_OPTS_STAGE2="$CONF_GCC_LINKER_OPTS_STAGE2 $GccUseLdOpt" LdCmd="$LD" +CFLAGS="$CFLAGS $GccUseLdOpt" AC_SUBST([LdCmd]) dnl ** Which nm to use? diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index 53c79e1..ac6af24 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -121,6 +121,7 @@ FIND_LD([$target],[GccUseLdOpt]) CONF_GCC_LINKER_OPTS_STAGE1="$CONF_GCC_LINKER_OPTS_STAGE1 $GccUseLdOpt" CONF_GCC_LINKER_OPTS_STAGE2="$CONF_GCC_LINKER_OPTS_STAGE2 $GccUseLdOpt" LdCmd="$LD" +CFLAGS="$CFLAGS $GccUseLdOpt" AC_SUBST([LdCmd]) FP_PROG_LD_IS_GNU From git at git.haskell.org Mon Jul 3 23:43:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 23:43:03 +0000 (UTC) Subject: [commit: ghc] master: rts: Fix isByteArrayPinned#'s treatment of large arrays (a6f3d1b) Message-ID: <20170703234303.B992E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a6f3d1b00e9c37a56cd4db9e519309e94a65d181/ghc >--------------------------------------------------------------- commit a6f3d1b00e9c37a56cd4db9e519309e94a65d181 Author: Ben Gamari Date: Mon Jul 3 19:09:03 2017 -0400 rts: Fix isByteArrayPinned#'s treatment of large arrays It should respond with True to both BF_PINNED and BF_LARGE byte arrays. However, previously it would only check the BF_PINNED flag. Test Plan: Validate Reviewers: simonmar, austin, erikd Subscribers: winterland1989, rwbarton, thomie GHC Trac Issues: #13894 Differential Revision: https://phabricator.haskell.org/D3685 >--------------------------------------------------------------- a6f3d1b00e9c37a56cd4db9e519309e94a65d181 rts/PrimOps.cmm | 5 +++-- testsuite/tests/rts/T13894.hs | 18 ++++++++++++++++++ testsuite/tests/rts/all.T | 1 + 3 files changed, 22 insertions(+), 2 deletions(-) diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm index dddba39..006c9de 100644 --- a/rts/PrimOps.cmm +++ b/rts/PrimOps.cmm @@ -147,10 +147,11 @@ stg_isByteArrayPinnedzh ( gcptr ba ) { W_ bd, flags; bd = Bdescr(ba); - // pinned byte arrays live in blocks with the BF_PINNED flag set. + // Pinned byte arrays live in blocks with the BF_PINNED flag set. + // We also consider BF_LARGE objects to be unmoveable. See #13894. // See the comment in Storage.c:allocatePinned. flags = TO_W_(bdescr_flags(bd)); - return (flags & BF_PINNED != 0); + return (flags & (BF_PINNED | BF_LARGE) != 0); } stg_isMutableByteArrayPinnedzh ( gcptr mba ) diff --git a/testsuite/tests/rts/T13894.hs b/testsuite/tests/rts/T13894.hs new file mode 100644 index 0000000..e09e908 --- /dev/null +++ b/testsuite/tests/rts/T13894.hs @@ -0,0 +1,18 @@ +-- Test that isByteArray# returns True for large but not explicitly pinned byte +-- arrays + +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} + +import Control.Monad +import GHC.Exts +import GHC.IO + +main :: IO () +main = do + pinned <- IO $ \s0 -> + case newByteArray# 1000000# s0 of + (# s1, arr# #) -> + case isMutableByteArrayPinned# arr# of + n# -> (# s1, isTrue# n# #) + unless pinned $ putStrLn "BAD" diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index e02f880..e819404 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -377,3 +377,4 @@ test('T12497', [ unless(opsys('mingw32'), skip) test('T12903', [when(opsys('mingw32'), skip)], compile_and_run, ['']) test('T13832', exit_code(1), compile_and_run, ['-threaded']) +test('T13894', normal, compile_and_run, ['']) From git at git.haskell.org Mon Jul 3 23:43:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 23:43:06 +0000 (UTC) Subject: [commit: ghc] master: Eagerly blackhole AP_STACKs (fd7a7a6) Message-ID: <20170703234306.843C83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fd7a7a6363d8dde1813bc23cb4ef00ebb70a49c0/ghc >--------------------------------------------------------------- commit fd7a7a6363d8dde1813bc23cb4ef00ebb70a49c0 Author: Ben Gamari Date: Mon Jul 3 19:10:07 2017 -0400 Eagerly blackhole AP_STACKs This fixes #13615. See the rather lengthy Note [AP_STACKs must be eagerly blackholed] for details. Reviewers: simonmar, austin, erikd, dfeuer Subscribers: duog, dfeuer, hsyl20, rwbarton, thomie GHC Trac Issues: #13615 Differential Revision: https://phabricator.haskell.org/D3695 >--------------------------------------------------------------- fd7a7a6363d8dde1813bc23cb4ef00ebb70a49c0 rts/Apply.cmm | 180 +++++++++++++++++++++++++++++++++++++++++++++++++++++ rts/RaiseAsync.c | 1 + rts/ThreadPaused.c | 9 +++ 3 files changed, 190 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 fd7a7a6363d8dde1813bc23cb4ef00ebb70a49c0 From git at git.haskell.org Mon Jul 3 23:43:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Jul 2017 23:43:10 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add testcase for #13615 (0836bfb) Message-ID: <20170703234310.4BCBC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0836bfbd480b00a690937060fc98df5e26453078/ghc >--------------------------------------------------------------- commit 0836bfbd480b00a690937060fc98df5e26453078 Author: Ben Gamari Date: Mon Jul 3 19:09:58 2017 -0400 testsuite: Add testcase for #13615 Reviewers: austin Subscribers: dfeuer, rwbarton, thomie GHC Trac Issues: #13615 Differential Revision: https://phabricator.haskell.org/D3696 >--------------------------------------------------------------- 0836bfbd480b00a690937060fc98df5e26453078 testsuite/tests/concurrent/T13615/Memo.hs | 57 ++++++++++++++++++ .../Parallel.hs} | 70 ++++++++-------------- testsuite/tests/concurrent/T13615/T13615.hs | 63 +++++++++++++++++++ testsuite/tests/concurrent/T13615/all.T | 11 ++++ 4 files changed, 155 insertions(+), 46 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 0836bfbd480b00a690937060fc98df5e26453078 From git at git.haskell.org Tue Jul 4 00:16:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Jul 2017 00:16:36 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: users-guide: Wibbles in shared libraries discussion (4bbf97b) Message-ID: <20170704001636.029A53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/4bbf97b62968ee097d0f1aa902bf1e9c553298f1/ghc >--------------------------------------------------------------- commit 4bbf97b62968ee097d0f1aa902bf1e9c553298f1 Author: Ben Gamari Date: Fri Jun 30 14:10:35 2017 -0400 users-guide: Wibbles in shared libraries discussion (cherry picked from commit 84d6831ae67ed7a543f7b14f04fc569e924ce1dd) >--------------------------------------------------------------- 4bbf97b62968ee097d0f1aa902bf1e9c553298f1 docs/users_guide/shared_libs.rst | 21 ++++++++++----------- 1 file changed, 10 insertions(+), 11 deletions(-) diff --git a/docs/users_guide/shared_libs.rst b/docs/users_guide/shared_libs.rst index 1d294b8..c0c54f1 100644 --- a/docs/users_guide/shared_libs.rst +++ b/docs/users_guide/shared_libs.rst @@ -117,12 +117,12 @@ the :ghc-flag:`-dynamic`, :ghc-flag:`-fPIC` and :ghc-flag:`-shared` flags: ghc --make -dynamic -shared -fPIC Foo.hs -o libfoo.so -As before, the ``-dynamic`` flag specifies that this library links -against the shared library versions of the rts and base package. The -``-fPIC`` flag is required for all code that will end up in a shared -library. The ``-shared`` flag specifies to make a shared library rather -than a program. To make this clearer we can break this down into -separate compilation and link steps: +As before, the :ghc-flag:`-dynamic` flag specifies that this library links +against the shared library versions of the ``rts`` and ``base`` package. The +:ghc-flag:`-fPIC` flag is required for all code that will end up in a shared +library. The :ghc-flag:`-shared` flag specifies to make a shared library rather +than a program. To make this clearer we can break this down into separate +compilation and link steps: .. code-block:: none @@ -130,12 +130,11 @@ separate compilation and link steps: ghc -dynamic -shared Foo.o -o libfoo.so In principle you can use :ghc-flag:`-shared` without :ghc-flag:`-dynamic` in the -link step. That means to statically link the rts all the base libraries into -your new shared library. This would make a very big, but standalone -shared library. On most platforms however that would require all the +link step. That means to statically link the runtime system and all of the base +libraries into your new shared library. This would make a very big, but +standalone shared library. On most platforms however that would require all the static libraries to have been built with :ghc-flag:`-fPIC` so that the code is -suitable to include into a shared library and we do not do that at the -moment. +suitable to include into a shared library and we do not do that at the moment. .. warning:: If your shared library exports a Haskell API then you cannot From git at git.haskell.org Tue Jul 4 00:16:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Jul 2017 00:16:41 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump array submodule to v0.5.2.0 (eb2ebdb) Message-ID: <20170704001641.7364A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/eb2ebdb475886b21cbd4ff8559e5de76de2a0345/ghc >--------------------------------------------------------------- commit eb2ebdb475886b21cbd4ff8559e5de76de2a0345 Author: Ben Gamari Date: Mon Jul 3 18:22:38 2017 -0400 Bump array submodule to v0.5.2.0 (cherry picked from commit 5aee331152c251525bc73b792660851dc5dddc29) >--------------------------------------------------------------- eb2ebdb475886b21cbd4ff8559e5de76de2a0345 libraries/array | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/array b/libraries/array index 1244242..9a23fea 160000 --- a/libraries/array +++ b/libraries/array @@ -1 +1 @@ -Subproject commit 1244242d895724ae53b13104ca225455ff08259c +Subproject commit 9a23feac0b78e713c0f7877066fa24dbc2217c20 From git at git.haskell.org Tue Jul 4 00:16:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Jul 2017 00:16:38 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: CmmParse: Emit source notes for assignments (8ab6d12) Message-ID: <20170704001638.BB8DB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/8ab6d12943f3547208abcfc1f9cf4d7e03a301ad/ghc >--------------------------------------------------------------- commit 8ab6d12943f3547208abcfc1f9cf4d7e03a301ad Author: Ben Gamari Date: Mon Jul 3 17:15:23 2017 -0400 CmmParse: Emit source notes for assignments Currently the line information for bare source C-- is rather spartan. These add notes for assignments, which tend to be useful to identify. Unfortunately, we had to settle for approximate source locations as none of the parsers in CmmParse return located things. However, I don't think it's worth changing this. (cherry picked from commit 0c1f905aea4d5a9e2e329ba6b57d5a009635ce3d) >--------------------------------------------------------------- 8ab6d12943f3547208abcfc1f9cf4d7e03a301ad compiler/cmm/CmmParse.y | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 6992581..82f30e9 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -593,9 +593,9 @@ stmt :: { CmmParse () } | lreg '=' expr ';' - { do reg <- $1; e <- $3; emitAssign reg e } + { do reg <- $1; e <- $3; withSourceNote $2 $4 (emitAssign reg e) } | type '[' expr ']' '=' expr ';' - { doStore $1 $3 $6 } + { withSourceNote $2 $7 (doStore $1 $3 $6) } -- Gah! We really want to say "foreign_results" but that causes -- a shift/reduce conflict with assignment. We either From git at git.haskell.org Tue Jul 4 00:16:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Jul 2017 00:16:46 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: rts: Fix uninitialised variable uses (6a51690) Message-ID: <20170704001646.E39923A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/6a516900ae29729f258ae8c2f4768e2d27e5facf/ghc >--------------------------------------------------------------- commit 6a516900ae29729f258ae8c2f4768e2d27e5facf Author: Ben Gamari Date: Mon Jul 3 19:07:59 2017 -0400 rts: Fix uninitialised variable uses Strangely gcc 5.4 compiling on amd64 (nixos) complained about these. Both warnings look correct, so I'm not sure why we haven't been seeing these up until now. Test Plan: Validate Reviewers: simonmar, austin, erikd Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3693 (cherry picked from commit 8f8d756c5a29217ff79154caa1696b6e572d186f) >--------------------------------------------------------------- 6a516900ae29729f258ae8c2f4768e2d27e5facf rts/Interpreter.c | 2 +- rts/sm/MarkWeak.c | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/rts/Interpreter.c b/rts/Interpreter.c index b60139e..02bf123 100644 --- a/rts/Interpreter.c +++ b/rts/Interpreter.c @@ -285,7 +285,7 @@ interpretBCO (Capability* cap) // that these entities are non-aliasable. register StgPtr Sp; // local state -- stack pointer register StgPtr SpLim; // local state -- stack lim pointer - register StgClosure *tagged_obj = 0, *obj; + register StgClosure *tagged_obj = 0, *obj = NULL; uint32_t n, m; LOAD_THREAD_STATE(); diff --git a/rts/sm/MarkWeak.c b/rts/sm/MarkWeak.c index e7dfd6e..89fc551 100644 --- a/rts/sm/MarkWeak.c +++ b/rts/sm/MarkWeak.c @@ -363,7 +363,7 @@ static void tidyThreadList (generation *gen) static void checkWeakPtrSanity(StgWeak *hd, StgWeak *tl) { StgWeak *w, *prev; - for (w = hd; w != NULL; prev = w, w = w->link) { + for (prev = NULL, w = hd; w != NULL; prev = w, w = w->link) { ASSERT(INFO_PTR_TO_STRUCT(UNTAG_CLOSURE((StgClosure*)w)->header.info)->type == WEAK || UNTAG_CLOSURE((StgClosure*)w)->header.info == &stg_DEAD_WEAK_info); checkClosure((StgClosure*)w); From git at git.haskell.org Tue Jul 4 00:16:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Jul 2017 00:16:44 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Allow per-argument documentation on pattern synonym signatures (dafa0df) Message-ID: <20170704001644.313BF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/dafa0dfad16dff51943a76c83c66f9814ca9a9ee/ghc >--------------------------------------------------------------- commit dafa0dfad16dff51943a76c83c66f9814ca9a9ee Author: alexbiehl Date: Mon Jul 3 16:53:10 2017 -0400 Allow per-argument documentation on pattern synonym signatures haddock-2.18 supports user defined pattern synonym signatures so this seems like a welcomed addition. Reviewers: austin, bgamari, mpickering Reviewed By: bgamari, mpickering Subscribers: rwbarton, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D3699 (cherry picked from commit 287a40564a7024b55daf0b063683ce889f8a18d9) >--------------------------------------------------------------- dafa0dfad16dff51943a76c83c66f9814ca9a9ee compiler/parser/Parser.y | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 542b996..a1135d3 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -1374,7 +1374,7 @@ where_decls :: { Located ([AddAnn] ,sL1 $3 (snd $ unLoc $3)) } pattern_synonym_sig :: { LSig RdrName } - : 'pattern' con_list '::' sigtype + : 'pattern' con_list '::' sigtypedoc {% ams (sLL $1 $> $ PatSynSig (unLoc $2) (mkLHsSigType $4)) [mj AnnPattern $1, mu AnnDcolon $3] } From git at git.haskell.org Tue Jul 4 00:16:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Jul 2017 00:16:50 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: rts: Fix isByteArrayPinned#'s treatment of large arrays (32dd9b8) Message-ID: <20170704001650.46FD23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/32dd9b8b84dfc2a395551f38bc3f1c8b470a2eb9/ghc >--------------------------------------------------------------- commit 32dd9b8b84dfc2a395551f38bc3f1c8b470a2eb9 Author: Ben Gamari Date: Mon Jul 3 19:09:03 2017 -0400 rts: Fix isByteArrayPinned#'s treatment of large arrays It should respond with True to both BF_PINNED and BF_LARGE byte arrays. However, previously it would only check the BF_PINNED flag. Test Plan: Validate Reviewers: simonmar, austin, erikd Subscribers: winterland1989, rwbarton, thomie GHC Trac Issues: #13894 Differential Revision: https://phabricator.haskell.org/D3685 (cherry picked from commit a6f3d1b00e9c37a56cd4db9e519309e94a65d181) >--------------------------------------------------------------- 32dd9b8b84dfc2a395551f38bc3f1c8b470a2eb9 rts/PrimOps.cmm | 5 +++-- testsuite/tests/rts/T13894.hs | 18 ++++++++++++++++++ testsuite/tests/rts/all.T | 1 + 3 files changed, 22 insertions(+), 2 deletions(-) diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm index 4baf63a..06b17c3 100644 --- a/rts/PrimOps.cmm +++ b/rts/PrimOps.cmm @@ -147,10 +147,11 @@ stg_isByteArrayPinnedzh ( gcptr ba ) { W_ bd, flags; bd = Bdescr(ba); - // pinned byte arrays live in blocks with the BF_PINNED flag set. + // Pinned byte arrays live in blocks with the BF_PINNED flag set. + // We also consider BF_LARGE objects to be unmoveable. See #13894. // See the comment in Storage.c:allocatePinned. flags = TO_W_(bdescr_flags(bd)); - return (flags & BF_PINNED != 0); + return (flags & (BF_PINNED | BF_LARGE) != 0); } stg_isMutableByteArrayPinnedzh ( gcptr mba ) diff --git a/testsuite/tests/rts/T13894.hs b/testsuite/tests/rts/T13894.hs new file mode 100644 index 0000000..e09e908 --- /dev/null +++ b/testsuite/tests/rts/T13894.hs @@ -0,0 +1,18 @@ +-- Test that isByteArray# returns True for large but not explicitly pinned byte +-- arrays + +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} + +import Control.Monad +import GHC.Exts +import GHC.IO + +main :: IO () +main = do + pinned <- IO $ \s0 -> + case newByteArray# 1000000# s0 of + (# s1, arr# #) -> + case isMutableByteArrayPinned# arr# of + n# -> (# s1, isTrue# n# #) + unless pinned $ putStrLn "BAD" diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index e02f880..e819404 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -377,3 +377,4 @@ test('T12497', [ unless(opsys('mingw32'), skip) test('T12903', [when(opsys('mingw32'), skip)], compile_and_run, ['']) test('T13832', exit_code(1), compile_and_run, ['-threaded']) +test('T13894', normal, compile_and_run, ['']) From git at git.haskell.org Tue Jul 4 00:16:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Jul 2017 00:16:56 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: testsuite: Add testcase for #13615 (d94aebd) Message-ID: <20170704001656.BA13C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/d94aebd369a78ae55ab2c078da79e4dc11fa9657/ghc >--------------------------------------------------------------- commit d94aebd369a78ae55ab2c078da79e4dc11fa9657 Author: Ben Gamari Date: Mon Jul 3 19:09:58 2017 -0400 testsuite: Add testcase for #13615 Reviewers: austin Subscribers: dfeuer, rwbarton, thomie GHC Trac Issues: #13615 Differential Revision: https://phabricator.haskell.org/D3696 (cherry picked from commit 0836bfbd480b00a690937060fc98df5e26453078) >--------------------------------------------------------------- d94aebd369a78ae55ab2c078da79e4dc11fa9657 testsuite/tests/concurrent/T13615/Memo.hs | 57 ++++++++++++++++++ .../Parallel.hs} | 70 ++++++++-------------- testsuite/tests/concurrent/T13615/T13615.hs | 63 +++++++++++++++++++ testsuite/tests/concurrent/T13615/all.T | 11 ++++ 4 files changed, 155 insertions(+), 46 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 d94aebd369a78ae55ab2c078da79e4dc11fa9657 From git at git.haskell.org Tue Jul 4 00:16:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Jul 2017 00:16:53 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Add -fuse-ld flag to CFLAGS during configure (0798908) Message-ID: <20170704001653.0894D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/0798908f1729629c2d90a56baae06919874b42a4/ghc >--------------------------------------------------------------- commit 0798908f1729629c2d90a56baae06919874b42a4 Author: Ben Gamari Date: Mon Jul 3 19:09:39 2017 -0400 Add -fuse-ld flag to CFLAGS during configure The decisions made by configure later in the script may depend upon the linker used. Consequently, it is important that configure uses the same linker as GHC will eventually use. For instance, on Nix I found that a program requiring `libpthread` would link fine with only `-lrt` when linked with BFD ld. However, with gold we needed to explicitly provide the `-lpthread` dependency. Presumably the former would happily loaded any `NEEDED` libraries whereas the latter wants them explicitly given. Regardless, since `configure`'s `NEED_PTHREAD_LIB` check didn't use the `-fuse-ld` flag that GHC would eventually use, we inferred the wrong value, resulting in link errors later in the build. Test Plan: Validate Reviewers: austin, hvr Subscribers: rwbarton, thomie, erikd GHC Trac Issues: #13541 Differential Revision: https://phabricator.haskell.org/D3694 (cherry picked from commit 960918bd1f7e3811845a525ba85bbd390ddf28c8) >--------------------------------------------------------------- 0798908f1729629c2d90a56baae06919874b42a4 configure.ac | 1 + distrib/configure.ac.in | 1 + 2 files changed, 2 insertions(+) diff --git a/configure.ac b/configure.ac index 27d879d..bad688a 100644 --- a/configure.ac +++ b/configure.ac @@ -501,6 +501,7 @@ FIND_LD([$target],[GccUseLdOpt]) CONF_GCC_LINKER_OPTS_STAGE1="$CONF_GCC_LINKER_OPTS_STAGE1 $GccUseLdOpt" CONF_GCC_LINKER_OPTS_STAGE2="$CONF_GCC_LINKER_OPTS_STAGE2 $GccUseLdOpt" LdCmd="$LD" +CFLAGS="$CFLAGS $GccUseLdOpt" AC_SUBST([LdCmd]) dnl ** Which nm to use? diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index ee9a105..3d2d90d 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -121,6 +121,7 @@ FIND_LD([$target],[GccUseLdOpt]) CONF_GCC_LINKER_OPTS_STAGE1="$CONF_GCC_LINKER_OPTS_STAGE1 $GccUseLdOpt" CONF_GCC_LINKER_OPTS_STAGE2="$CONF_GCC_LINKER_OPTS_STAGE2 $GccUseLdOpt" LdCmd="$LD" +CFLAGS="$CFLAGS $GccUseLdOpt" AC_SUBST([LdCmd]) FP_PROG_LD_IS_GNU From git at git.haskell.org Tue Jul 4 00:16:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Jul 2017 00:16:59 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Eagerly blackhole AP_STACKs (c1c0985) Message-ID: <20170704001659.816433A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/c1c0985416a6f9766c03d361449f556905bf8e1d/ghc >--------------------------------------------------------------- commit c1c0985416a6f9766c03d361449f556905bf8e1d Author: Ben Gamari Date: Mon Jul 3 19:10:07 2017 -0400 Eagerly blackhole AP_STACKs This fixes #13615. See the rather lengthy Note [AP_STACKs must be eagerly blackholed] for details. Reviewers: simonmar, austin, erikd, dfeuer Subscribers: duog, dfeuer, hsyl20, rwbarton, thomie GHC Trac Issues: #13615 Differential Revision: https://phabricator.haskell.org/D3695 (cherry picked from commit fd7a7a6363d8dde1813bc23cb4ef00ebb70a49c0) >--------------------------------------------------------------- c1c0985416a6f9766c03d361449f556905bf8e1d rts/Apply.cmm | 180 +++++++++++++++++++++++++++++++++++++++++++++++++++++ rts/RaiseAsync.c | 1 + rts/ThreadPaused.c | 16 +++-- 3 files changed, 193 insertions(+), 4 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 c1c0985416a6f9766c03d361449f556905bf8e1d From git at git.haskell.org Tue Jul 4 16:42:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Jul 2017 16:42:51 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump haddock submodule (d1aa359) Message-ID: <20170704164251.8B4063A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/d1aa359c0d34200c22912d8f6974d5a6307ffb3f/ghc >--------------------------------------------------------------- commit d1aa359c0d34200c22912d8f6974d5a6307ffb3f Author: Ben Gamari Date: Tue Jul 4 08:49:45 2017 -0400 Bump haddock submodule >--------------------------------------------------------------- d1aa359c0d34200c22912d8f6974d5a6307ffb3f utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index af3e6c7..22cbf4d 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit af3e6c7c027389df18b15ee9a9d72ffc97dc1852 +Subproject commit 22cbf4d9509d3b537e6c2fcf4c95ae73d930b9aa From git at git.haskell.org Wed Jul 5 08:11:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Jul 2017 08:11:39 +0000 (UTC) Subject: [commit: ghc] master: rts/sm/Storage.c: tweak __clear_cache proto for clang (9492703) Message-ID: <20170705081139.63DE03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9492703a5862ee8623455209e50344cf8c4de077/ghc >--------------------------------------------------------------- commit 9492703a5862ee8623455209e50344cf8c4de077 Author: Sergei Trofimovich Date: Wed Jul 5 08:36:08 2017 +0100 rts/sm/Storage.c: tweak __clear_cache proto for clang clang defines '__clear_cache' slightly differently from gcc: rts/sm/Storage.c:1349:13: error: error: conflicting types for '__clear_cache' | 1349 | extern void __clear_cache(char * begin, char * end); | ^ extern void __clear_cache(char * begin, char * end); ^ note: '__clear_cache' is a builtin with type 'void (void *, void *)' Reported by Moritz Angermann. While at it used '__builtin___clear_cache' if advertised by clang. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 9492703a5862ee8623455209e50344cf8c4de077 rts/sm/Storage.c | 15 +++++++++++++-- 1 file changed, 13 insertions(+), 2 deletions(-) diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c index e243517..f518856 100644 --- a/rts/sm/Storage.c +++ b/rts/sm/Storage.c @@ -1341,7 +1341,13 @@ StgWord calcTotalCompactW (void) #include #endif -#if defined(__GNUC__) +#if defined(__CLANG__) +/* clang defines __clear_cache as a builtin on some platforms. + * For example on armv7-linux-androideabi. The type slightly + * differs from gcc. + */ +extern void __clear_cache(void * begin, void * end); +#elif defined(__GNUC__) /* __clear_cache is a libgcc function. * It existed before __builtin___clear_cache was introduced. * See Trac #8562. @@ -1360,11 +1366,16 @@ void flushExec (W_ len, AdjustorExecutable exec_addr) #elif (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && defined(ios_HOST_OS) /* On iOS we need to use the special 'sys_icache_invalidate' call. */ sys_icache_invalidate(exec_addr, len); +#elif defined(__CLANG__) +# if __has_builtin(__builtin___clear_cache) + __builtin___clear_cache((void*)begin, (void*)end); +# else + __clear_cache((void*)begin, (void*)end); +# endif #elif defined(__GNUC__) /* For all other platforms, fall back to a libgcc builtin. */ unsigned char* begin = (unsigned char*)exec_addr; unsigned char* end = begin + len; - /* __builtin___clear_cache is supported since GNU C 4.3.6. * We pick 4.4 to simplify condition a bit. */ From git at git.haskell.org Wed Jul 5 08:15:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Jul 2017 08:15:48 +0000 (UTC) Subject: [commit: ghc] master: Revert "rts/sm/Storage.c: tweak __clear_cache proto for clang" (7040660) Message-ID: <20170705081548.480933A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7040660528f597c12f8bc49ca87f3697ab3d3653/ghc >--------------------------------------------------------------- commit 7040660528f597c12f8bc49ca87f3697ab3d3653 Author: Sergei Trofimovich Date: Wed Jul 5 09:13:09 2017 +0100 Revert "rts/sm/Storage.c: tweak __clear_cache proto for clang" This reverts commit 9492703a5862ee8623455209e50344cf8c4de077. Incomplete patch (missing begin, end assignments). >--------------------------------------------------------------- 7040660528f597c12f8bc49ca87f3697ab3d3653 rts/sm/Storage.c | 15 ++------------- 1 file changed, 2 insertions(+), 13 deletions(-) diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c index f518856..e243517 100644 --- a/rts/sm/Storage.c +++ b/rts/sm/Storage.c @@ -1341,13 +1341,7 @@ StgWord calcTotalCompactW (void) #include #endif -#if defined(__CLANG__) -/* clang defines __clear_cache as a builtin on some platforms. - * For example on armv7-linux-androideabi. The type slightly - * differs from gcc. - */ -extern void __clear_cache(void * begin, void * end); -#elif defined(__GNUC__) +#if defined(__GNUC__) /* __clear_cache is a libgcc function. * It existed before __builtin___clear_cache was introduced. * See Trac #8562. @@ -1366,16 +1360,11 @@ void flushExec (W_ len, AdjustorExecutable exec_addr) #elif (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && defined(ios_HOST_OS) /* On iOS we need to use the special 'sys_icache_invalidate' call. */ sys_icache_invalidate(exec_addr, len); -#elif defined(__CLANG__) -# if __has_builtin(__builtin___clear_cache) - __builtin___clear_cache((void*)begin, (void*)end); -# else - __clear_cache((void*)begin, (void*)end); -# endif #elif defined(__GNUC__) /* For all other platforms, fall back to a libgcc builtin. */ unsigned char* begin = (unsigned char*)exec_addr; unsigned char* end = begin + len; + /* __builtin___clear_cache is supported since GNU C 4.3.6. * We pick 4.4 to simplify condition a bit. */ From git at git.haskell.org Wed Jul 5 08:15:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Jul 2017 08:15:51 +0000 (UTC) Subject: [commit: ghc] master: rts/sm/Storage.c: tweak __clear_cache proto for clang (3eeb55e) Message-ID: <20170705081551.1C79A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3eeb55e9578f6eaebccf27170eb1324990affb51/ghc >--------------------------------------------------------------- commit 3eeb55e9578f6eaebccf27170eb1324990affb51 Author: Sergei Trofimovich Date: Wed Jul 5 08:36:08 2017 +0100 rts/sm/Storage.c: tweak __clear_cache proto for clang clang defines '__clear_cache' slightly differently from gcc: rts/sm/Storage.c:1349:13: error: error: conflicting types for '__clear_cache' | 1349 | extern void __clear_cache(char * begin, char * end); | ^ extern void __clear_cache(char * begin, char * end); ^ note: '__clear_cache' is a builtin with type 'void (void *, void *)' Reported by Moritz Angermann. While at it used '__builtin___clear_cache' if advertised by clang. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 3eeb55e9578f6eaebccf27170eb1324990affb51 rts/sm/Storage.c | 17 +++++++++++++++-- 1 file changed, 15 insertions(+), 2 deletions(-) diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c index e243517..7b97c01 100644 --- a/rts/sm/Storage.c +++ b/rts/sm/Storage.c @@ -1341,7 +1341,13 @@ StgWord calcTotalCompactW (void) #include #endif -#if defined(__GNUC__) +#if defined(__CLANG__) +/* clang defines __clear_cache as a builtin on some platforms. + * For example on armv7-linux-androideabi. The type slightly + * differs from gcc. + */ +extern void __clear_cache(void * begin, void * end); +#elif defined(__GNUC__) /* __clear_cache is a libgcc function. * It existed before __builtin___clear_cache was introduced. * See Trac #8562. @@ -1360,11 +1366,18 @@ void flushExec (W_ len, AdjustorExecutable exec_addr) #elif (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && defined(ios_HOST_OS) /* On iOS we need to use the special 'sys_icache_invalidate' call. */ sys_icache_invalidate(exec_addr, len); +#elif defined(__CLANG__) + unsigned char* begin = (unsigned char*)exec_addr; + unsigned char* end = begin + len; +# if __has_builtin(__builtin___clear_cache) + __builtin___clear_cache((void*)begin, (void*)end); +# else + __clear_cache((void*)begin, (void*)end); +# endif #elif defined(__GNUC__) /* For all other platforms, fall back to a libgcc builtin. */ unsigned char* begin = (unsigned char*)exec_addr; unsigned char* end = begin + len; - /* __builtin___clear_cache is supported since GNU C 4.3.6. * We pick 4.4 to simplify condition a bit. */ From git at git.haskell.org Wed Jul 5 18:49:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Jul 2017 18:49:30 +0000 (UTC) Subject: [commit: ghc] master: rts: Address AP_STACK comment suggestion from Simon (555e5cc) Message-ID: <20170705184930.73DE53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/555e5cc48b6c2608ae8d4bd3b2a5bd2ef63236ab/ghc >--------------------------------------------------------------- commit 555e5cc48b6c2608ae8d4bd3b2a5bd2ef63236ab Author: Ben Gamari Date: Tue Jul 4 12:45:30 2017 -0400 rts: Address AP_STACK comment suggestion from Simon >--------------------------------------------------------------- 555e5cc48b6c2608ae8d4bd3b2a5bd2ef63236ab rts/Apply.cmm | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/rts/Apply.cmm b/rts/Apply.cmm index a0b498a..36a9859 100644 --- a/rts/Apply.cmm +++ b/rts/Apply.cmm @@ -506,9 +506,9 @@ Here we have two threads (TSO 1 and TSO 2) which are in currently pausing (e.g. in threadPaused). Since they are pausing, their stacks are headed by a pointer to the continuation code which we will run on resumption (go and fun, respectively). We also see that there are two thunks on the heap: THUNK A and -THUNK B where THUNK A is reachable from THUNK B (for instance, as an argument or -free variable). We see that thread 1 has THUNK A under evaluation, and both -threads have THUNK B under evaluation. +THUNK B where THUNK B depends upon THUNK A (as in, evaluation of B will force +A). We see that thread 1 has THUNK A under evaluation, and both threads have +THUNK B under evaluation. As each thread enters threadPaused, threadPaused will walk its stack looking for duplicate computation (see Note [suspend duplicate work], although there is some From git at git.haskell.org Wed Jul 5 18:49:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Jul 2017 18:49:33 +0000 (UTC) Subject: [commit: ghc] master: mkDocs: Don't install *.ps (4997177) Message-ID: <20170705184933.298A43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/499717756f010eb6796747a74f948454ad17c061/ghc >--------------------------------------------------------------- commit 499717756f010eb6796747a74f948454ad17c061 Author: Ben Gamari Date: Wed Jul 5 14:48:26 2017 -0400 mkDocs: Don't install *.ps We now longer produce PostScript output. >--------------------------------------------------------------- 499717756f010eb6796747a74f948454ad17c061 distrib/mkDocs/mkDocs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/distrib/mkDocs/mkDocs b/distrib/mkDocs/mkDocs index fbb0a6f..d185b43 100755 --- a/distrib/mkDocs/mkDocs +++ b/distrib/mkDocs/mkDocs @@ -40,7 +40,7 @@ do done mv index.html ../../../../.. cd .. -mv *.pdf *.ps ../../../.. +mv *.pdf ../../../.. cd ../../../.. [ "$NO_CLEAN" -eq 0 ] && rm -r inst [ "$NO_CLEAN" -eq 0 ] && rm -r windows From git at git.haskell.org Wed Jul 5 18:50:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Jul 2017 18:50:20 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: mkDocs: Don't install *.ps (0302c80) Message-ID: <20170705185020.1D8F73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/0302c8046ed4e79a9921c338f115624838b9989b/ghc >--------------------------------------------------------------- commit 0302c8046ed4e79a9921c338f115624838b9989b Author: Ben Gamari Date: Wed Jul 5 14:48:26 2017 -0400 mkDocs: Don't install *.ps We now longer produce PostScript output. >--------------------------------------------------------------- 0302c8046ed4e79a9921c338f115624838b9989b distrib/mkDocs/mkDocs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/distrib/mkDocs/mkDocs b/distrib/mkDocs/mkDocs index fbb0a6f..d185b43 100755 --- a/distrib/mkDocs/mkDocs +++ b/distrib/mkDocs/mkDocs @@ -40,7 +40,7 @@ do done mv index.html ../../../../.. cd .. -mv *.pdf *.ps ../../../.. +mv *.pdf ../../../.. cd ../../../.. [ "$NO_CLEAN" -eq 0 ] && rm -r inst [ "$NO_CLEAN" -eq 0 ] && rm -r windows From git at git.haskell.org Thu Jul 6 02:23:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Jul 2017 02:23:24 +0000 (UTC) Subject: [commit: ghc] wip/faster-stats: Speed up core size and core stats (760dde9) Message-ID: <20170706022324.346E33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/faster-stats Link : http://ghc.haskell.org/trac/ghc/changeset/760dde942165d1567c6a2ee0a9e7d6891dfef15d/ghc >--------------------------------------------------------------- commit 760dde942165d1567c6a2ee0a9e7d6891dfef15d Author: David Feuer Date: Wed Jul 5 22:22:54 2017 -0400 Speed up core size and core stats Summary: When calculating core size and core stats, we previously calculated sizes/stats for sub-parts and then added them. It should be faster to thread an accumulator through. Reviewers: austin, bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3483 >--------------------------------------------------------------- 760dde942165d1567c6a2ee0a9e7d6891dfef15d compiler/coreSyn/CoreStats.hs | 77 ++++++++++++++++++++++++------------------ compiler/types/TyCoRep.hs | 78 ++++++++++++++++++++++++++----------------- 2 files changed, 91 insertions(+), 64 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 760dde942165d1567c6a2ee0a9e7d6891dfef15d From git at git.haskell.org Thu Jul 6 02:23:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Jul 2017 02:23:29 +0000 (UTC) Subject: [commit: ghc] wip/faster-stats: Merge branch 'wip/faster-stats' of git.haskell.org:ghc into wip/faster-stats (182fbf5) Message-ID: <20170706022329.B06C63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/faster-stats Link : http://ghc.haskell.org/trac/ghc/changeset/182fbf59cb568eaa32487902eba31df619d6e673/ghc >--------------------------------------------------------------- commit 182fbf59cb568eaa32487902eba31df619d6e673 Merge: b94eeb5 5cdeddd Author: David Feuer Date: Wed Jul 5 22:24:42 2017 -0400 Merge branch 'wip/faster-stats' of git.haskell.org:ghc into wip/faster-stats >--------------------------------------------------------------- 182fbf59cb568eaa32487902eba31df619d6e673 From git at git.haskell.org Thu Jul 6 02:23:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Jul 2017 02:23:26 +0000 (UTC) Subject: [commit: ghc] wip/faster-stats: Silly (b94eeb5) Message-ID: <20170706022326.E0F033A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/faster-stats Link : http://ghc.haskell.org/trac/ghc/changeset/b94eeb5cd1fadcc2a2df90e8e128ab0a08f68cfd/ghc >--------------------------------------------------------------- commit b94eeb5cd1fadcc2a2df90e8e128ab0a08f68cfd Author: David Feuer Date: Wed Jul 5 22:24:10 2017 -0400 Silly >--------------------------------------------------------------- b94eeb5cd1fadcc2a2df90e8e128ab0a08f68cfd compiler/coreSyn/CoreStats.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/coreSyn/CoreStats.hs b/compiler/coreSyn/CoreStats.hs index 5827f16..afcc5e5 100644 --- a/compiler/coreSyn/CoreStats.hs +++ b/compiler/coreSyn/CoreStats.hs @@ -37,6 +37,7 @@ instance Outputable CoreStats where text "joins:" <+> intWithCommas i5 <> char '/' <> intWithCommas (i4 + i5) ]) + plusCS :: CoreStats -> CoreStats -> CoreStats plusCS (CS { cs_tm = p1, cs_ty = q1, cs_co = r1, cs_vb = v1, cs_jb = j1 }) (CS { cs_tm = p2, cs_ty = q2, cs_co = r2, cs_vb = v2, cs_jb = j2 }) From git at git.haskell.org Thu Jul 6 02:23:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Jul 2017 02:23:33 +0000 (UTC) Subject: [commit: ghc] wip/faster-stats's head updated: Merge branch 'wip/faster-stats' of git.haskell.org:ghc into wip/faster-stats (182fbf5) Message-ID: <20170706022333.8A1953A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/faster-stats' 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" 70191f5 Add a test for #11272 56de222 Add a test for #12600 1269aff includes/Stg.h: '#if sparch_HOST_ARCH' -> '#if defined(sparch_HOST_ARCH)' 2a971e3 Update unix submodule 20c39b7 ProfilerReportJson.c: fix out-of-bounds access 230416f rts: annotate switch/case with '/* fallthrough */' d5414dd rts/linker/ElfTypes.h: restore powerps (and others) support e527fc2 Stress test for nested module hierarchies 06ad87e Revert "Stress test for nested module hierarchies" ffbcfff Stress test for nested module hierarchies 8bf50d5 Revert "Use a deterministic map for imp_dep_mods" bc06655 users-guide: Document -g flag 49012eb Print warnings on parser failures (#12610). efd113f testsuite: Add testcase for T13658 2c21d74 Kill off unused IfaceType.eqIfaceType fea9a75 Tiny refactor cec7d58 Fix the pure unifier d9e9a9b Fix #13703 by correctly using munged names in ghc-pkg. d6461f9 Handle type-lets better 7b52525 Insert missing newline 433b80d Ensure that insolubles are fully rewritten c039624 Fix Haddock markup 875159c Comments and white space only d06cb96 Refactor freeNamesIfDecl 8fe37a0 Account for IfUnpackCo in freeNamesIfDecl 2501fb7 Fix scoping of data cons during kind checking 4e0e120 Modern type signature style in Module 40210c3 Improve error msg for simplifier tick exhaustion 0a754e6 Failing test case for #13734 0102e2b CNF: Silence pointer fix-up message unless gc debugging is enabled 53c78be Compile modules that are needed by template haskell, even with -fno-code. 80d5190 base: Explicitly mark Data.Either.{left,right} as INLINABLE 8646648 Correctly expand lines with multiple tabs 5b8f95d A few documentation fixes 2108460 Pretty-print strict record fields from ifaces correctly 82eab62 Bump to LLVM 4.0 6f8c3ce Fix levity polymorphism docs 5179fd4 Add missing "do" to example in arrow docs. d6686a2 Ensure package.cache is newer than registration files after make install 0440af6 Rewrite boot in Python 83ee930 fix a memory leak in osNumaMask dac49bd Handle file targets in missing home modules warning 139ef04 Add "header" to GHC_COLORS 17fef39 Testcase for #13719 2bc3a05 Testcase for type family consistency checks 033f897 Extend ModuleSet with useful functions 1fd06de aclocal.m4: allow override of dllwrap and windres when cross-compiling 432a1f1 mk/config.mk.in: lower -O2 optimization down to -O1 on UNREG 1076010 ghc.mk: rename installed ghc-stage1 on non-windows 6166b59 base: Fix a few TODOs in Typeable.Internal a29132e rts: Make compact debugging output depend upon compact debug flag 0b4b4a3 Typos in comments and manual [ci skip] 1013194 Comments only c997738 Pattern synonyms and higher rank types 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 b5c73a9 Modern type signature style in UniqSet 8bfab43 Efficient checks for stable modules 69d9081 Faster checkFamInstConsistency d39a340 aclocal.m4: add support for versioned darwin triplets 750a25f A few typos [ci skip] 35c7ea8 [iserv] move forkIO 5164cce aclocal: Fix regression in linker detection 93489cd Better import library support for Windows d0fb0df Add a flag reference entry for -XTypeInType bf775e9 Remove references to static flags in flag reference 2abe54e Make GHCi work when RebindableSyntax is enabled 811a298 GHC.Stats cleanup a786b13 Use lengthIs and friends in more places ff363bd ghc.mk: Ensure that ghc-pkg path is quoted 6597f08 Test Trac #13784 a65dfea Make the MR warning more accurage c9eb438 Desugar modules compiled with -fno-code 8e6ec0f Udate hsSyn AST to use Trees that Grow e77b9a2 Typo in output of remote slave startup [merge cand] 92a4f90 Spelling typos 2b74bd9 Stop the specialiser generating loopy code ef07010 Test Trac #13750 bca56bd Fix slash escaping in cwrapper.c 5984729 Fix a lost-wakeup bug in BLACKHOLE handling (#13751) 3e8ab7c Linker: Fix whitespace 1c76dd8 Revert "Make LLVM output robust to -dead_strip on mach-o platforms" ffd948e Bump nofib submodule 7bb2aa0 testsuite: Add performance test, Naperian 1c83fd8 [linker] fix armv7 & add aarch64 cd8f4b9 Check target libtool 3ee3822 Refactor temp files cleanup 56ef544 Add tcRnGetNameToInstancesIndex b10d3f3 Don't pass -dcore-lint to haddock in Haddock.mk b2b4160 Correct optimization flags documentation 0d94a3e linker: Fix cast-to-uint64_t 7e0ef11 Fix a bug in -foptimal-applicative-do 8f72608 users-guide: Document multi-line DEPRECATED pragmas f942f65 Improve getNameToInstancesIndex dcdc391 Fix #13807 - foreign import nondeterminism 6ddb3aa Add perf test for #12545 9a3ca8d Support signatures at the kind level in Template Haskell 2088d0b Stop forcing everything in coreBindsSize af9612b Make -w less aggressive (Trac #12056) 0058a34 Typos [ci skip] ece39c3 Fix Haddock markup 430137c Add mapMG to allow making ModuleGraph abstract 9849403 base: Validate input in setNumCapabilities dc8e686 Fix the treatment of 'closed' definitions fda094d Provide way to build using existing C compiler on Windows. d6cecde Remove the Windows GCC driver. 559a0c5 Fix out-of-date comments in TyCoRep 8573100 Look through type synonyms in existential contexts when deriving Functor df32880 Typofix in Data.Type.Equality comments b9f9670 rts: Ensure that new capability count is > 0 e12ea39 rts: A bit of cleanup around the eventlog 04ca036 testsuite: Add testcase for #13822 ee9232524 Add fixity declaration for :~~: 23f47b1 Add T9630 bea18a0 Fix GCC 7 warning in the RTS 990928f Don't expose fingerprints from Type.Reflection 271e0f0 Add test cases for #13821 a9b62a3 configure: Look for objdump on OpenBSD and AIX 6a2264d cmm/CmmLayoutStack: avoid generating unnecessary reloads 564a31f Reword documentation region overlap documentation for copying mutable arrays 986deaa Add missing -Wdeprecations flag to the users guide 5c93df9 Improve comments on AbsBinds b1fa386 Fix note reference [ci skip] 6dd1257 UNREG: use __builtin___clear_cache where available 88263f9 base: Export Fingerprint accessors from Type.Reflection.Unsafe c85cd9b Show only the number of modules in ghci c8370a8 change filtering of variables in extract_hs_tv_bndrs (fixes #13782) c6fe403 Revert "UNREG: use __builtin___clear_cache where available" d1d3e98 rts: Suppress unused gcc_clear_cache warning 76769bd Revert "rts: Suppress unused gcc_clear_cache warning" a9bf7d4 Fix typo 34b7f63 UNREG: use __builtin___clear_cache where available 84cf095 compiler: Eliminate pprTrace in SPT entry addition codepath e13edee testsuite: Fix cabal01 test 398a444 Add fixity declaration for Data.List.NonEmpty.!! 3c4537e Fix pretty-printing of zero-argument lambda expressions 9077120 Use actual universal tvs in check for naughty record selectors 42eee6e Hoopl: remove dependency on Hoopl package faefa7e documentation: fix trac issue #12978 a48464a users guide: Rephrasing 904255e DWARF: Use .short to render half-machine-words 4bd4f56 rts: Always collect stats 86abe0e users-guide/debug-info: Fix incorrect DWARF tags b8f8736 base/inputReady: Whitespace cleanup 914962c Update docs to reflect changes to DeriveDataTypeable 9ef909d Allow bytecode interpreter to make unsafe foreign calls 12a3c39 testsuite: Add broken test for #13871 1346525 typecheck: Consider types containing coercions non-Typeable 1e47126 rts: Clarify whitehole logic in threadPaused 6567c81 Treat banged bindings as FunBinds b070858 Make module membership on ModuleGraph faster 22b917e Revert "Make module membership on ModuleGraph faster" 4bdac33 Fix the in-scope set in TcHsType.instantiateTyN c80920d Do zonking in tcLHsKindSig fae672f Fix constraint solving for forall-types 87c5fdb Zap stable unfoldings in worker/wrapper 78c80c2 Typos in comments and manual [ci skip] 3f9422c More typos in comments [ci skip] 7097f94 Remove unneeded import 54ccf0c remove dead function 'tcInstBinders' 3b0e755 Fix lexically-scoped type variables 58c781d Revert "Remove the Windows GCC driver." c2fb6e8 Typos in comments c3f12ec Fix T13701 allocation for Linux 7de2c07 users-guide: Document FFI safety guarantees 6171b0b configure: Check for binutils #17166 007f255 Allow optional instance keyword in associated type family instances 625143f configure: Coerce gcc to use $LD instead of system default 9b514de rts/RetainerProfile: Const-correctness fixes 1ef4156 Prevent ApplicativeDo from applying to strict pattern matches (#13875) 0592318 Fix paper link in MVar docs [ci skip] 544ac0d rename tcInstBinder(s)X to tcInstBinder(s) 84d6831a users-guide: Wibbles in shared libraries discussion 287a405 Allow per-argument documentation on pattern synonym signatures 1a9c3c4 Implement recompilation checking for -fignore-asserts f9c6d53 Tag the FUN before making a PAP (#13767) c3a7862 Fix #13311 by using tcSplitNestedSigmaTys in the right place d55bea1 Fix -fno-code for modules that use -XQuasiQuotes 0c1f905 CmmParse: Emit source notes for assignments 5aee331 Bump array submodule to v0.5.2.0 8f8d756 rts: Fix uninitialised variable uses af403b2 ApplicativeDo: document behaviour with strict patterns (#13875) ef63ff2 configure: Remove --with-curses-includes flag a6f3d1b rts: Fix isByteArrayPinned#'s treatment of large arrays 960918b Add -fuse-ld flag to CFLAGS during configure 0836bfb testsuite: Add testcase for #13615 fd7a7a6 Eagerly blackhole AP_STACKs 9492703 rts/sm/Storage.c: tweak __clear_cache proto for clang 7040660 Revert "rts/sm/Storage.c: tweak __clear_cache proto for clang" 3eeb55e rts/sm/Storage.c: tweak __clear_cache proto for clang 555e5cc rts: Address AP_STACK comment suggestion from Simon 4997177 mkDocs: Don't install *.ps 760dde9 Speed up core size and core stats b94eeb5 Silly 182fbf5 Merge branch 'wip/faster-stats' of git.haskell.org:ghc into wip/faster-stats From git at git.haskell.org Thu Jul 6 05:48:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Jul 2017 05:48:31 +0000 (UTC) Subject: [commit: ghc] wip/faster-stats: Add type signature (15b43ab) Message-ID: <20170706054831.5D3763A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/faster-stats Link : http://ghc.haskell.org/trac/ghc/changeset/15b43ab9732be8a5712df0fdfd270c60e6def2fd/ghc >--------------------------------------------------------------- commit 15b43ab9732be8a5712df0fdfd270c60e6def2fd Author: David Feuer Date: Thu Jul 6 01:47:29 2017 -0400 Add type signature >--------------------------------------------------------------- 15b43ab9732be8a5712df0fdfd270c60e6def2fd compiler/types/TyCoRep.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index e4fe0e8..15cd6a5 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -2844,6 +2844,7 @@ typeSizePlus (TyConApp _ ts) = \acc0 -> typeSizePlus (CastTy ty co) = typeSizePlus ty `sizerPlus` coercionSizePlus co typeSizePlus (CoercionTy co) = coercionSizePlus co +coercionSizePlus :: Coercion -> Int -> Int coercionSizePlus (Refl _ ty) = typeSizePlus ty coercionSizePlus (TyConAppCo _ _ args) = \acc0 -> foldl' (\acc arg -> coercionSizePlus arg acc) (acc0 + 1) args From git at git.haskell.org Thu Jul 6 07:02:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Jul 2017 07:02:26 +0000 (UTC) Subject: [commit: ghc] master: lowercase clang (f3979b7) Message-ID: <20170706070226.2A2353A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f3979b7fbd83e85301ba2f028936fb7c50a48f42/ghc >--------------------------------------------------------------- commit f3979b7fbd83e85301ba2f028936fb7c50a48f42 Author: Moritz Angermann Date: Thu Jul 6 11:31:20 2017 +0800 lowercase clang >--------------------------------------------------------------- f3979b7fbd83e85301ba2f028936fb7c50a48f42 rts/sm/Storage.c | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c index 7b97c01..ffaed5f 100644 --- a/rts/sm/Storage.c +++ b/rts/sm/Storage.c @@ -1341,7 +1341,7 @@ StgWord calcTotalCompactW (void) #include #endif -#if defined(__CLANG__) +#if defined(__clang__) /* clang defines __clear_cache as a builtin on some platforms. * For example on armv7-linux-androideabi. The type slightly * differs from gcc. @@ -1366,7 +1366,7 @@ void flushExec (W_ len, AdjustorExecutable exec_addr) #elif (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && defined(ios_HOST_OS) /* On iOS we need to use the special 'sys_icache_invalidate' call. */ sys_icache_invalidate(exec_addr, len); -#elif defined(__CLANG__) +#elif defined(__clang__) unsigned char* begin = (unsigned char*)exec_addr; unsigned char* end = begin + len; # if __has_builtin(__builtin___clear_cache) From git at git.haskell.org Thu Jul 6 08:50:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Jul 2017 08:50:06 +0000 (UTC) Subject: [commit: ghc] master: Typos in comments [ci skip] (99adcc8) Message-ID: <20170706085006.18FD13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/99adcc8804e91161b35ff1d0e5f718d18fcaa66a/ghc >--------------------------------------------------------------- commit 99adcc8804e91161b35ff1d0e5f718d18fcaa66a Author: Gabor Greif Date: Thu Jul 6 10:48:52 2017 +0200 Typos in comments [ci skip] >--------------------------------------------------------------- 99adcc8804e91161b35ff1d0e5f718d18fcaa66a compiler/hsSyn/HsImpExp.hs | 2 +- compiler/main/HscMain.hs | 2 +- compiler/typecheck/TcHsType.hs | 2 +- docs/users_guide/ffi-chap.rst | 2 +- includes/stg/Ticky.h | 2 +- rts/Apply.cmm | 2 +- rts/PrimOps.cmm | 2 +- utils/hpc/HpcFlags.hs | 2 +- 8 files changed, 8 insertions(+), 8 deletions(-) diff --git a/compiler/hsSyn/HsImpExp.hs b/compiler/hsSyn/HsImpExp.hs index 57f74e3..79ff287 100644 --- a/compiler/hsSyn/HsImpExp.hs +++ b/compiler/hsSyn/HsImpExp.hs @@ -139,7 +139,7 @@ instance (OutputableBndrId pass) => Outputable (ImportDecl pass) where ************************************************************************ -} --- | A name in an import or export specfication which may have adornments. Used +-- | A name in an import or export specification which may have adornments. Used -- primarily for accurate pretty printing of ParsedSource, and API Annotation -- placement. data IEWrappedName name diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index b8bd76b..0f0ea4d 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -1119,7 +1119,7 @@ markUnsafeInfer tcg_env whyUnsafe = do mkPlainWarnMsg dflags (warnUnsafeOnLoc dflags) (whyUnsafe' dflags)) liftIO $ writeIORef (tcg_safeInfer tcg_env) (False, whyUnsafe) - -- NOTE: Only wipe trust when not in an explicity safe haskell mode. Other + -- NOTE: Only wipe trust when not in an explicitly safe haskell mode. Other -- times inference may be on but we are in Trustworthy mode -- so we want -- to record safe-inference failed but not wipe the trust dependencies. case safeHaskell dflags == Sf_None of diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 9653685..3766c6b 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -1845,7 +1845,7 @@ tcHsPartialSigType ctxt sig_ty ; explicit_tvs <- mapM zonkTyCoVarKind explicit_tvs ; let all_tvs = implicit_tvs ++ explicit_tvs - -- The implicit_tvs alraedy have zonked kinds + -- The implicit_tvs already have zonked kinds ; theta <- mapM zonkTcType theta ; tau <- zonkTcType tau diff --git a/docs/users_guide/ffi-chap.rst b/docs/users_guide/ffi-chap.rst index 616df29..bd5ca3d 100644 --- a/docs/users_guide/ffi-chap.rst +++ b/docs/users_guide/ffi-chap.rst @@ -34,7 +34,7 @@ The FFI addendum stipulates that an implementation is free to implement an arbitrary thread and may be subject to concurrent garbage collection). This greatly constrains library authors since it implies that it is never safe to pass any heap object reference to a foreign function, even if invoked with an -``unsafe`` call. For instance, it is often desireable to pass an unpinned +``unsafe`` call. For instance, it is often desirable to pass an unpinned ``ByteArray#``\s directly to native code to avoid making an otherwise-unnecessary copy. However, this can only be done safely under ``unsafe`` call semantics as otherwise the array may be moved by the garbage diff --git a/includes/stg/Ticky.h b/includes/stg/Ticky.h index 5e2c372..2341dba 100644 --- a/includes/stg/Ticky.h +++ b/includes/stg/Ticky.h @@ -30,7 +30,7 @@ extern W_ ticky_entry_ctrs[]; extern W_ top_ct[]; #endif -/* The rest are not explicity declared in rts/Ticky.c. Instead +/* The rest are not explicitly declared in rts/Ticky.c. Instead we use the same trick as in the former StgTicky.h: recycle the same declarations for both extern decls (which are included everywhere) and initializations (which only happen once) diff --git a/rts/Apply.cmm b/rts/Apply.cmm index 36a9859..64f0a9b 100644 --- a/rts/Apply.cmm +++ b/rts/Apply.cmm @@ -462,7 +462,7 @@ middle of an ST action multiple times, resulting in duplication of effects. In short, the construction of an AP_STACK allows us to suspend a computation which should not be duplicated. When running with lazy blackholing, we can then enter this AP_STACK multiple times, duplicating the computation with potentially -disasterous consequences. +disastrous consequences. For instance, consider the case of a simple ST program which computes a sum using in─place mutation, diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm index 006c9de..3d4bea4 100644 --- a/rts/PrimOps.cmm +++ b/rts/PrimOps.cmm @@ -148,7 +148,7 @@ stg_isByteArrayPinnedzh ( gcptr ba ) W_ bd, flags; bd = Bdescr(ba); // Pinned byte arrays live in blocks with the BF_PINNED flag set. - // We also consider BF_LARGE objects to be unmoveable. See #13894. + // We also consider BF_LARGE objects to be immovable. See #13894. // See the comment in Storage.c:allocatePinned. flags = TO_W_(bdescr_flags(bd)); return (flags & (BF_PINNED | BF_LARGE) != 0); diff --git a/utils/hpc/HpcFlags.hs b/utils/hpc/HpcFlags.hs index dd1d9f7..2d78375 100644 --- a/utils/hpc/HpcFlags.hs +++ b/utils/hpc/HpcFlags.hs @@ -194,7 +194,7 @@ data Plugin = Plugin { name :: String -- filterModules takes a list of candidate modules, -- and -- * excludes the excluded modules --- * includes the rest if there are no explicity included modules +-- * includes the rest if there are no explicitly included modules -- * otherwise, accepts just the included modules. allowModule :: Flags -> String -> Bool From git at git.haskell.org Fri Jul 7 00:18:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Jul 2017 00:18:41 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Basic metrics collection and command line options working (44bbba6) Message-ID: <20170707001841.898163A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/44bbba648247255b57b7c633bf9c5f495691348f/ghc >--------------------------------------------------------------- commit 44bbba648247255b57b7c633bf9c5f495691348f Author: Jared Weakly Date: Thu Jul 6 17:16:49 2017 -0700 Basic metrics collection and command line options working >--------------------------------------------------------------- 44bbba648247255b57b7c633bf9c5f495691348f libraries/array | 2 +- libraries/hoopl | 1 + testsuite/driver/runtests.py | 36 ++++++++++++++++++++++++------------ testsuite/driver/testglobals.py | 11 ++++++++++- testsuite/driver/testlib.py | 6 ++++++ testsuite/driver/testutil.py | 4 ++++ testsuite/mk/test.mk | 12 ++++++++++++ 7 files changed, 58 insertions(+), 14 deletions(-) diff --git a/libraries/array b/libraries/array index 9a23fea..f7b69e9 160000 --- a/libraries/array +++ b/libraries/array @@ -1 +1 @@ -Subproject commit 9a23feac0b78e713c0f7877066fa24dbc2217c20 +Subproject commit f7b69e9cb914cb69bbede5264729523fb8669db1 diff --git a/libraries/hoopl b/libraries/hoopl new file mode 160000 index 0000000..ac24864 --- /dev/null +++ b/libraries/hoopl @@ -0,0 +1 @@ +Subproject commit ac24864c2db7951a6f34674e2b11b69d37ef84ff diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index 7e4f375..c09b063 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -42,18 +42,21 @@ def signal_handler(signal, frame): # cmd-line options long_options = [ - "configfile=", # config file - "config=", # config field - "rootdir=", # root of tree containing tests (default: .) - "summary-file=", # file in which to save the (human-readable) summary - "no-print-summary=", # should we print the summary? - "only=", # just this test (can be give multiple --only= flags) - "way=", # just this way - "skipway=", # skip this way - "threads=", # threads to run simultaneously - "check-files-written", # check files aren't written by multiple tests - "verbose=", # verbose (0,1,2 so far) - "skip-perf-tests", # skip performance tests + "configfile=", # config file + "config=", # config field + "rootdir=", # root of tree containing tests (default: .) + "summary-file=", # file in which to save the (human-readable) summary + "no-print-summary=", # should we print the summary? + "only=", # just this test (can be give multiple --only= flags) + "way=", # just this way + "skipway=", # skip this way + "threads=", # threads to run simultaneously + "check-files-written", # check files aren't written by multiple tests + "verbose=", # verbose (0,1,2 so far) + "skip-perf-tests", # skip performance tests + "only-perf-tests", # Only do performance tests + "use-git-notes", # use git notes to store metrics. NOTE: This is expected to become the default and will eventually be taken out. + "TEST_ENV=", # Override default chosen test-env. ] opts, args = getopt.getopt(sys.argv[1:], "e:", long_options) @@ -110,12 +113,21 @@ for opt,arg in opts: if opt == '--skip-perf-tests': config.skip_perf_tests = True + if opt == '--only-perf-tests': + config.only_perf_tests = True + + if opt == '--use-git-notes': + config.use_git_notes = True + if opt == '--verbose': if arg not in ["0","1","2","3","4","5"]: sys.stderr.write("ERROR: requested verbosity %s not supported, use 0,1,2,3,4 or 5" % arg) sys.exit(1) config.verbose = int(arg) + if opt == '--TEST_ENV': + config.TEST_ENV = arg + config.cygwin = False config.msys = False diff --git a/testsuite/driver/testglobals.py b/testsuite/driver/testglobals.py index fc050e6..bd8eefe 100644 --- a/testsuite/driver/testglobals.py +++ b/testsuite/driver/testglobals.py @@ -117,6 +117,16 @@ class TestConfig: # Should we skip performance tests self.skip_perf_tests = False + # Only do performance tests + self.only_perf_tests = False + + # Should we dump statistics to git notes? + self.use_git_notes = False + # To accumulate the metrics for the git notes + self.accumulate_metrics = [] + # Has the user defined a custom test environment? Local is default. + self.TEST_ENV = 'local' + global config config = TestConfig() @@ -283,4 +293,3 @@ default_testopts = TestOptions() # (bug, directory, name) of tests marked broken global brokens brokens = [] - diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index b730685..887cfe5 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1084,6 +1084,7 @@ def stats( name, way, stats_file ): # Check -t stats info def checkStats(name, way, stats_file, range_fields): + full_name = name + '(' + way + ')' result = passed() @@ -1107,6 +1108,11 @@ def checkStats(name, way, stats_file, range_fields): deviation = round(((float(val) * 100)/ expected) - 100, 1) + # Add val into the git note if option is set. + if config.use_git_notes: + test_env = config.TEST_ENV + config.accumulate_metrics.append(test_env + '\t' + name + '\t' + way + '\t' + field + '\t' + str(val)) + if val < lowerBound: print(field, 'value is too low:') print('(If this is because you have improved GHC, please') diff --git a/testsuite/driver/testutil.py b/testsuite/driver/testutil.py index d35fb81..084ef7e 100644 --- a/testsuite/driver/testutil.py +++ b/testsuite/driver/testutil.py @@ -47,6 +47,10 @@ def lndir(srcdir, dstdir): os.mkdir(dst) lndir(src, dst) +# def git_append(note): +# def print_metrics(): +# print(config.accumulate_metrics) + # On Windows, os.symlink is not defined with Python 2.7, but is in Python 3 # when using msys2, as GHC does. Unfortunately, only Administrative users have # the privileges necessary to create symbolic links by default. Consequently we diff --git a/testsuite/mk/test.mk b/testsuite/mk/test.mk index a44e200..9896883 100644 --- a/testsuite/mk/test.mk +++ b/testsuite/mk/test.mk @@ -195,6 +195,18 @@ ifeq "$(SKIP_PERF_TESTS)" "YES" RUNTEST_OPTS += --skip-perf-tests endif +ifeq "$(ONLY_PERF_TESTS)" "YES" +RUNTEST_OPTS += --only-perf-tests +endif + +ifeq "$(USE_GIT_NOTES)" "YES" +RUNTEST_OPTS += --use-git-notes +endif + +ifneq "$(TEST_ENV)" "" +RUNTEST_OPTS += --TEST_ENV="$(TEST_ENV)" +endif + ifeq "$(CLEANUP)" "0" RUNTEST_OPTS += -e config.cleanup=False else ifeq "$(CLEANUP)" "NO" From git at git.haskell.org Fri Jul 7 00:18:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Jul 2017 00:18:44 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite's head updated: Basic metrics collection and command line options working (44bbba6) Message-ID: <20170707001844.32C0D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/perf-testsuite' now includes: 0d94a3e linker: Fix cast-to-uint64_t 7e0ef11 Fix a bug in -foptimal-applicative-do 8f72608 users-guide: Document multi-line DEPRECATED pragmas f942f65 Improve getNameToInstancesIndex dcdc391 Fix #13807 - foreign import nondeterminism 6ddb3aa Add perf test for #12545 9a3ca8d Support signatures at the kind level in Template Haskell 2088d0b Stop forcing everything in coreBindsSize af9612b Make -w less aggressive (Trac #12056) 0058a34 Typos [ci skip] ece39c3 Fix Haddock markup 430137c Add mapMG to allow making ModuleGraph abstract 9849403 base: Validate input in setNumCapabilities dc8e686 Fix the treatment of 'closed' definitions fda094d Provide way to build using existing C compiler on Windows. d6cecde Remove the Windows GCC driver. 559a0c5 Fix out-of-date comments in TyCoRep 8573100 Look through type synonyms in existential contexts when deriving Functor df32880 Typofix in Data.Type.Equality comments b9f9670 rts: Ensure that new capability count is > 0 e12ea39 rts: A bit of cleanup around the eventlog 04ca036 testsuite: Add testcase for #13822 ee9232524 Add fixity declaration for :~~: 23f47b1 Add T9630 bea18a0 Fix GCC 7 warning in the RTS 990928f Don't expose fingerprints from Type.Reflection 271e0f0 Add test cases for #13821 a9b62a3 configure: Look for objdump on OpenBSD and AIX 6a2264d cmm/CmmLayoutStack: avoid generating unnecessary reloads 564a31f Reword documentation region overlap documentation for copying mutable arrays 986deaa Add missing -Wdeprecations flag to the users guide 5c93df9 Improve comments on AbsBinds b1fa386 Fix note reference [ci skip] 6dd1257 UNREG: use __builtin___clear_cache where available 88263f9 base: Export Fingerprint accessors from Type.Reflection.Unsafe c85cd9b Show only the number of modules in ghci c8370a8 change filtering of variables in extract_hs_tv_bndrs (fixes #13782) c6fe403 Revert "UNREG: use __builtin___clear_cache where available" d1d3e98 rts: Suppress unused gcc_clear_cache warning 76769bd Revert "rts: Suppress unused gcc_clear_cache warning" a9bf7d4 Fix typo 34b7f63 UNREG: use __builtin___clear_cache where available 84cf095 compiler: Eliminate pprTrace in SPT entry addition codepath e13edee testsuite: Fix cabal01 test 398a444 Add fixity declaration for Data.List.NonEmpty.!! 3c4537e Fix pretty-printing of zero-argument lambda expressions 9077120 Use actual universal tvs in check for naughty record selectors 42eee6e Hoopl: remove dependency on Hoopl package faefa7e documentation: fix trac issue #12978 a48464a users guide: Rephrasing 904255e DWARF: Use .short to render half-machine-words 4bd4f56 rts: Always collect stats 86abe0e users-guide/debug-info: Fix incorrect DWARF tags b8f8736 base/inputReady: Whitespace cleanup 914962c Update docs to reflect changes to DeriveDataTypeable 9ef909d Allow bytecode interpreter to make unsafe foreign calls 12a3c39 testsuite: Add broken test for #13871 1346525 typecheck: Consider types containing coercions non-Typeable 1e47126 rts: Clarify whitehole logic in threadPaused 6567c81 Treat banged bindings as FunBinds b070858 Make module membership on ModuleGraph faster 22b917e Revert "Make module membership on ModuleGraph faster" 4bdac33 Fix the in-scope set in TcHsType.instantiateTyN c80920d Do zonking in tcLHsKindSig fae672f Fix constraint solving for forall-types 87c5fdb Zap stable unfoldings in worker/wrapper 78c80c2 Typos in comments and manual [ci skip] 3f9422c More typos in comments [ci skip] 7097f94 Remove unneeded import 54ccf0c remove dead function 'tcInstBinders' 3b0e755 Fix lexically-scoped type variables 58c781d Revert "Remove the Windows GCC driver." c2fb6e8 Typos in comments c3f12ec Fix T13701 allocation for Linux 7de2c07 users-guide: Document FFI safety guarantees 6171b0b configure: Check for binutils #17166 007f255 Allow optional instance keyword in associated type family instances 625143f configure: Coerce gcc to use $LD instead of system default 9b514de rts/RetainerProfile: Const-correctness fixes 1ef4156 Prevent ApplicativeDo from applying to strict pattern matches (#13875) 0592318 Fix paper link in MVar docs [ci skip] 544ac0d rename tcInstBinder(s)X to tcInstBinder(s) 84d6831a users-guide: Wibbles in shared libraries discussion 287a405 Allow per-argument documentation on pattern synonym signatures 1a9c3c4 Implement recompilation checking for -fignore-asserts f9c6d53 Tag the FUN before making a PAP (#13767) c3a7862 Fix #13311 by using tcSplitNestedSigmaTys in the right place d55bea1 Fix -fno-code for modules that use -XQuasiQuotes 0c1f905 CmmParse: Emit source notes for assignments 5aee331 Bump array submodule to v0.5.2.0 8f8d756 rts: Fix uninitialised variable uses af403b2 ApplicativeDo: document behaviour with strict patterns (#13875) ef63ff2 configure: Remove --with-curses-includes flag a6f3d1b rts: Fix isByteArrayPinned#'s treatment of large arrays 960918b Add -fuse-ld flag to CFLAGS during configure 0836bfb testsuite: Add testcase for #13615 fd7a7a6 Eagerly blackhole AP_STACKs 9492703 rts/sm/Storage.c: tweak __clear_cache proto for clang 7040660 Revert "rts/sm/Storage.c: tweak __clear_cache proto for clang" 3eeb55e rts/sm/Storage.c: tweak __clear_cache proto for clang 555e5cc rts: Address AP_STACK comment suggestion from Simon 4997177 mkDocs: Don't install *.ps f3979b7 lowercase clang 99adcc8 Typos in comments [ci skip] 44bbba6 Basic metrics collection and command line options working From git at git.haskell.org Fri Jul 7 23:02:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Jul 2017 23:02:50 +0000 (UTC) Subject: [commit: ghc] master: Implement split-sections support for windows. (bd4fdc6) Message-ID: <20170707230250.7078B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bd4fdc6aa34a85268f3e9a2bd3f4142a97724ce4/ghc >--------------------------------------------------------------- commit bd4fdc6aa34a85268f3e9a2bd3f4142a97724ce4 Author: Tamar Christina Date: Sun Mar 26 19:05:46 2017 +0100 Implement split-sections support for windows. Summary: Initial implementation of split-section on Windows. This also corrects section namings and uses the platform convention of `$` instead of `.` to separate sections. Implementation is based on @awson's patches to binutils. Binutils requires some extra help when compiling the libraries for GHCi usage. We drop the `-T` and use implicit scripts to amend the linker scripts instead of replacing it. Because of these very large GHCi object files, we need big-obj support, which will be added by another patch. Test Plan: ./validate Reviewers: awson, austin, bgamari Subscribers: dfeuer, rwbarton, thomie, snowleopard, #ghc_windows_task_force GHC Trac Issues: #12913 Differential Revision: https://phabricator.haskell.org/D3383 >--------------------------------------------------------------- bd4fdc6aa34a85268f3e9a2bd3f4142a97724ce4 compiler/llvmGen/LlvmCodeGen/Data.hs | 20 ++++++++++---- compiler/nativeGen/PprBase.hs | 31 ++++++++++++++-------- docs/users_guide/8.4.1-notes.rst | 3 +++ .../{merge_sections.ld => merge_sections_pe.ld} | 20 +++++++------- mk/config.mk.in | 2 +- rules/build-package-way.mk | 8 +++++- 6 files changed, 56 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 bd4fdc6aa34a85268f3e9a2bd3f4142a97724ce4 From git at git.haskell.org Sat Jul 8 09:01:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Jul 2017 09:01:08 +0000 (UTC) Subject: [commit: ghc] master: aclocal.m4: allow arbitrary string in toolchain triplets (c2303df) Message-ID: <20170708090108.ACEA33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c2303dff95aa174021a1950656fdf9a1cf983959/ghc >--------------------------------------------------------------- commit c2303dff95aa174021a1950656fdf9a1cf983959 Author: Sergei Trofimovich Date: Sat Jul 8 09:47:12 2017 +0100 aclocal.m4: allow arbitrary string in toolchain triplets Canonical triplets have a form of --[-] Checking for vendor is almost never correct as it's an arbitrary string. It's useful to have multiple "vendors" to denote otherwise the same (WRT , , ) target: --target=x86_64-pc-linux-gnu --target=x86_64-unknown-linux-gnu --target=x86_64-ghc80-linux-gnu --target=x86_64-ghchead-linux-gnu Do not fail unknown vendors. Only emit a warning. Ideally configure checks should never use "vendor". Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- c2303dff95aa174021a1950656fdf9a1cf983959 aclocal.m4 | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 001f813..1d9c09b 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -230,8 +230,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS], dec|none|unknown|hp|apple|next|sun|sgi|ibm|montavista|portbld) ;; *) - echo "Unknown vendor [$]1" - exit 1 + AC_MSG_WARN([Unknown vendor [$]1]) ;; esac } From git at git.haskell.org Sat Jul 8 11:22:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Jul 2017 11:22:40 +0000 (UTC) Subject: [commit: ghc] master: Fix typos in Bag.hs [ci skip] (e1146ed) Message-ID: <20170708112240.72D4E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e1146ed5d822e79b121b057c49ac13b61bcca93a/ghc >--------------------------------------------------------------- commit e1146ed5d822e79b121b057c49ac13b61bcca93a Author: Ömer Sinan Ağacan Date: Sat Jul 8 14:22:17 2017 +0300 Fix typos in Bag.hs [ci skip] >--------------------------------------------------------------- e1146ed5d822e79b121b057c49ac13b61bcca93a compiler/utils/Bag.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/utils/Bag.hs b/compiler/utils/Bag.hs index 5771162..fffbb6e 100644 --- a/compiler/utils/Bag.hs +++ b/compiler/utils/Bag.hs @@ -286,7 +286,7 @@ mapAndUnzipBagM f (ListBag xs) = do ts <- mapM f xs let (rs,ss) = unzip ts return (ListBag rs, ListBag ss) -mapAccumBagL ::(acc -> x -> (acc, y)) -- ^ combining funcction +mapAccumBagL ::(acc -> x -> (acc, y)) -- ^ combining function -> acc -- ^ initial state -> Bag x -- ^ inputs -> (acc, Bag y) -- ^ final state, outputs @@ -299,7 +299,7 @@ mapAccumBagL f s (ListBag xs) = let (s', xs') = mapAccumL f s xs in (s', ListBag xs') mapAccumBagLM :: Monad m - => (acc -> x -> m (acc, y)) -- ^ combining funcction + => (acc -> x -> m (acc, y)) -- ^ combining function -> acc -- ^ initial state -> Bag x -- ^ inputs -> m (acc, Bag y) -- ^ final state, outputs From git at git.haskell.org Sat Jul 8 16:00:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Jul 2017 16:00:40 +0000 (UTC) Subject: [commit: ghc] master: Big-obj support for the Windows runtime linker (81377e9) Message-ID: <20170708160040.6E2453A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/81377e9e4bd52256946114d9c1dd966d5e3e7692/ghc >--------------------------------------------------------------- commit 81377e9e4bd52256946114d9c1dd966d5e3e7692 Author: Tamar Christina Date: Sat Jul 8 09:57:55 2017 +0100 Big-obj support for the Windows runtime linker Summary: The normal object file on Windows has a limit of `2^16` sections that can be in an object-file. The `big-obj` format raises this to `2^32` sections. The implementation is made difficult because we now need to support two header formats and two section formats that differ only by a single element size within each. The element that's different is in the middle of the structs and since the structs are used to map regions of memory directly, it means we need to know which struct it is when we do the mapping or pointer arithmetics. This is the final Object-Code format which Windows compilers can generate which we do not support yet in GHCI. All other major compilers on the platforms can produce it and all linkers consume it (bfd and lld). See http://tinyurl.com/bigobj This patch abstracts away retrieving the fields to functions which all take an struct which describes which object format is currently being parsed. These functions are always in-lined as they're small but would looks messy being copy-pasted everywhere. Test Plan: ./validate and new test `big-obj` ``` Tamar at Rage MINGW64 /r $ gcc -c -Wa,-mbig-obj foo.c -o foo.o Tamar at Rage MINGW64 /r $ objdump -h foo.o foo.o: file format pe-bigobj-x86-64 Sections: Idx Name Size VMA LMA File off Algn 0 .text 00000010 0000000000000000 0000000000000000 00000128 2**4 CONTENTS, ALLOC, LOAD, READONLY, CODE 1 .data 00000000 0000000000000000 0000000000000000 00000000 2**4 ALLOC, LOAD, DATA 2 .bss 00000000 0000000000000000 0000000000000000 00000000 2**4 ALLOC 3 .xdata 00000008 0000000000000000 0000000000000000 00000138 2**2 CONTENTS, ALLOC, LOAD, READONLY, DATA 4 .pdata 0000000c 0000000000000000 0000000000000000 00000140 2**2 CONTENTS, ALLOC, LOAD, RELOC, READONLY, DATA 5 .rdata$zzz 00000030 0000000000000000 0000000000000000 0000014c 2**4 CONTENTS, ALLOC, LOAD, READONLY, DATA Tamar at Rage MINGW64 /r $ echo main | ~/ghc/inplace/bin/ghc-stage2.exe --interactive bar.hs foo.o GHCi, version 8.3.20170430: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( bar.hs, interpreted ) Ok, modules loaded: Main. *Main> 17 *Main> Leaving GHCi. ``` Reviewers: austin, bgamari, erikd, simonmar Subscribers: awson, rwbarton, thomie, #ghc_windows_task_force GHC Trac Issues: #13815 Differential Revision: https://phabricator.haskell.org/D3523 >--------------------------------------------------------------- 81377e9e4bd52256946114d9c1dd966d5e3e7692 docs/users_guide/8.4.1-notes.rst | 2 + rts/linker/PEi386.c | 624 ++++++++++++++++----- rts/linker/PEi386.h | 52 +- testsuite/tests/ghci/linking/dyn/Makefile | 5 + testsuite/tests/ghci/linking/dyn/all.T | 4 + .../foo_dll.c => ghci/linking/dyn/big-obj-c.c} | 2 +- testsuite/tests/ghci/linking/dyn/big-obj.hs | 3 + .../linking/dyn/big-obj.stdout} | 0 8 files changed, 539 insertions(+), 153 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 81377e9e4bd52256946114d9c1dd966d5e3e7692 From git at git.haskell.org Sat Jul 8 19:22:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Jul 2017 19:22:45 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Preserve file attributes when copying bindist into place (62768f1) Message-ID: <20170708192245.91D583A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/62768f17c58d8c8ca142709471790e5eeb5b558d/ghc >--------------------------------------------------------------- commit 62768f17c58d8c8ca142709471790e5eeb5b558d Author: Ben Gamari Date: Sat Jul 8 15:20:39 2017 -0400 Preserve file attributes when copying bindist into place >--------------------------------------------------------------- 62768f17c58d8c8ca142709471790e5eeb5b558d Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index ab92bfe..ec9e1d9 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -284,7 +284,7 @@ def testGhc(params) { sh "${makeCmd} install" } else { sh "mkdir -p \"${instDir}\"" - sh "cp -R * \"${instDir}\"" + sh "cp -a * \"${instDir}\"" } } From git at git.haskell.org Mon Jul 10 11:04:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Jul 2017 11:04:20 +0000 (UTC) Subject: [commit: ghc] master: Pretty-printer no longer butchers function arrow fixity (c506f83) Message-ID: <20170710110420.58A3A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c506f8353755333e21d5ee35bc71d2c8f9ddcb1b/ghc >--------------------------------------------------------------- commit c506f8353755333e21d5ee35bc71d2c8f9ddcb1b Author: Alan Zimmerman Date: Mon Jul 10 13:00:36 2017 +0200 Pretty-printer no longer butchers function arrow fixity It now correctly prints the parens around '(Int -> Int)' in {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where $([d| f :: Either Int (Int -> Int) f = undefined |]) Closes #13942 >--------------------------------------------------------------- c506f8353755333e21d5ee35bc71d2c8f9ddcb1b compiler/hsSyn/Convert.hs | 1 + testsuite/tests/printer/Makefile | 4 ++++ testsuite/tests/printer/T13942.hs | 36 +++++++++++++++++++++++++++++++++++ testsuite/tests/printer/T13942.stdout | 12 ++++++++++++ testsuite/tests/printer/all.T | 1 + 5 files changed, 54 insertions(+) diff --git a/compiler/hsSyn/Convert.hs b/compiler/hsSyn/Convert.hs index 8b7af27..8fc903b 100644 --- a/compiler/hsSyn/Convert.hs +++ b/compiler/hsSyn/Convert.hs @@ -1330,6 +1330,7 @@ mk_apps head_ty (ty:tys) = ; mk_apps (HsAppTy head_ty' p_ty) tys } where add_parens t@(L _ HsAppTy{}) = returnL (HsParTy t) + add_parens t@(L _ HsFunTy{}) = returnL (HsParTy t) add_parens t = return t wrap_apps :: LHsType GhcPs -> CvtM (LHsType GhcPs) diff --git a/testsuite/tests/printer/Makefile b/testsuite/tests/printer/Makefile index 9cb968f..1c2f299 100644 --- a/testsuite/tests/printer/Makefile +++ b/testsuite/tests/printer/Makefile @@ -209,3 +209,7 @@ T13050p: .PHONY: T13550 T13550: $(CHECK_PPR) "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" T13550.hs + +.PHONY: T13942 +T13942: + $(CHECK_PPR) "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" T13942.hs diff --git a/testsuite/tests/printer/T13942.hs b/testsuite/tests/printer/T13942.hs new file mode 100644 index 0000000..8899e1c --- /dev/null +++ b/testsuite/tests/printer/T13942.hs @@ -0,0 +1,36 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# OPTIONS_GHC -ddump-splices -dsuppress-uniques #-} +module T13942 where + +$([d| f :: Either Int (Int -> Int) + f = undefined + |]) + +{- + +Note: to debug + +~/inplace/bin/ghc-stage2 --interactive +load the following +-------------------------------------- +import Language.Haskell.TH + +foo :: IO () +foo = do + r <- runQ ([d| f :: Either Int (Int -> Int) + f = undefined + |]) + print r + +---------------------------------------- +foo +[SigD f_0 (AppT (AppT (ConT Data.Either.Either) (ConT GHC.Types.Int)) (AppT (AppT ArrowT (ConT GHC.Types.Int)) (ConT GHC.Types.Int))) +,ValD (VarP f_0) (NormalB (VarE GHC.Err.undefined)) []] + +[SigD f_0 + (AppT (AppT (ConT Data.Either.Either) + (ConT GHC.Types.Int)) + (AppT (AppT ArrowT + (ConT GHC.Types.Int)) + (ConT GHC.Types.Int))) +-} diff --git a/testsuite/tests/printer/T13942.stdout b/testsuite/tests/printer/T13942.stdout new file mode 100644 index 0000000..2d0f617 --- /dev/null +++ b/testsuite/tests/printer/T13942.stdout @@ -0,0 +1,12 @@ +T13942.hs:(5,3)-(7,6): Splicing declarations + [d| f :: Either Int (Int -> Int) + f = undefined |] + ======> + f :: Either Int (Int -> Int) + f = undefined +T13942.ppr.hs:(4,3)-(5,22): Splicing declarations + [d| f :: Either Int (Int -> Int) + f = undefined |] + ======> + f :: Either Int (Int -> Int) + f = undefined diff --git a/testsuite/tests/printer/all.T b/testsuite/tests/printer/all.T index c939e49..a71d6e3 100644 --- a/testsuite/tests/printer/all.T +++ b/testsuite/tests/printer/all.T @@ -49,3 +49,4 @@ test('Ppr048', ignore_stderr, run_command, ['$MAKE -s --no-print-directory ppr04 test('T13199', ignore_stderr, run_command, ['$MAKE -s --no-print-directory T13199']) test('T13050p', ignore_stderr, run_command, ['$MAKE -s --no-print-directory T13050p']) test('T13550', ignore_stderr, run_command, ['$MAKE -s --no-print-directory T13550']) +test('T13942', ignore_stderr, run_command, ['$MAKE -s --no-print-directory T13942']) From git at git.haskell.org Tue Jul 11 17:42:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 17:42:20 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Decrease T13701 allocations (4f69013) Message-ID: <20170711174220.D3A9B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4f6901334c3ced4ecc0c211f4c2ba5f56db9eab5/ghc >--------------------------------------------------------------- commit 4f6901334c3ced4ecc0c211f4c2ba5f56db9eab5 Author: Ben Gamari Date: Tue Jul 11 13:19:53 2017 -0400 testsuite: Decrease T13701 allocations >--------------------------------------------------------------- 4f6901334c3ced4ecc0c211f4c2ba5f56db9eab5 testsuite/tests/perf/compiler/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 10fa715..f8b93aa 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -1132,9 +1132,9 @@ test('T13701', [ compiler_stats_num_field('bytes allocated', [(platform('x86_64-apple-darwin'), 2217187888, 10), (platform('x86_64-unknown-linux'), 2467546360, 10), - (wordsize(64), 2188045288, 10), # initial: 2511285600 # 2017-06-23: 2188045288 treat banged variable bindings as FunBinds + # 2017-07-11: 2187920960 ]), pre_cmd('./genT13701'), extra_files(['genT13701']), From git at git.haskell.org Tue Jul 11 17:42:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 17:42:23 +0000 (UTC) Subject: [commit: ghc] master: user-guide: Various fixes to FFI section (31ceaba) Message-ID: <20170711174223.946EE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/31ceaba3edac536d8a8d97d49bb797d4f5bedac6/ghc >--------------------------------------------------------------- commit 31ceaba3edac536d8a8d97d49bb797d4f5bedac6 Author: Ben Gamari Date: Wed Jul 5 15:01:47 2017 -0400 user-guide: Various fixes to FFI section >--------------------------------------------------------------- 31ceaba3edac536d8a8d97d49bb797d4f5bedac6 docs/users_guide/ffi-chap.rst | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/docs/users_guide/ffi-chap.rst b/docs/users_guide/ffi-chap.rst index bd5ca3d..684435c 100644 --- a/docs/users_guide/ffi-chap.rst +++ b/docs/users_guide/ffi-chap.rst @@ -15,16 +15,16 @@ definition is part of the Haskell Report on FFI support is enabled by default, but can be enabled or disabled explicitly with the :ghc-flag:`-XForeignFunctionInterface` flag. -GHC implements a number of GHC-specific extensions to the FFI Addendum. -These extensions are described in :ref:`ffi-ghcexts`, but please note -that programs using these features are not portable. Hence, these +GHC implements a number of GHC-specific extensions to the FFI Chapter of the +Haskell 2010 Report. These extensions are described in :ref:`ffi-ghcexts`, but +please note that programs using these features are not portable. Hence, these features should be avoided where possible. The FFI libraries are documented in the accompanying library documentation; see for example the :base-ref:`Foreign ` module. -GHC differences to the FFI Addendum ------------------------------------ +GHC differences to the FFI Chapter +---------------------------------- Guaranteed call safety ~~~~~~~~~~~~~~~~~~~~~~ @@ -41,7 +41,7 @@ otherwise-unnecessary copy. However, this can only be done safely under collector in the middle of the call. In previous releases, GHC would take advantage of the freedom afforded by the -Addendum by performing ``safe`` foreign calls in place of ``unsafe`` calls in +Chapter by performing ``safe`` foreign calls in place of ``unsafe`` calls in the bytecode interpreter. This meant that some packages which worked when compiled would fail under GHCi (e.g. :ghc-ticket:`13730`). @@ -52,8 +52,8 @@ bytecode interpreter. .. _ffi-ghcexts: -GHC extensions to the FFI Addendum ----------------------------------- +GHC extensions to the FFI Chapter +--------------------------------- The FFI features that are described in this section are specific to GHC. Your code will not be portable to other compilers if you use them. @@ -62,7 +62,7 @@ Unboxed types ~~~~~~~~~~~~~ The following unboxed types may be used as basic foreign types (see FFI -Addendum, Section 3.2): ``Int#``, ``Word#``, ``Char#``, ``Float#``, +Chapter, Section 8.6): ``Int#``, ``Word#``, ``Char#``, ``Float#``, ``Double#``, ``Addr#``, ``StablePtr# a``, ``MutableByteArray#``, ``ForeignObj#``, and ``ByteArray#``. From git at git.haskell.org Tue Jul 11 17:42:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 17:42:26 +0000 (UTC) Subject: [commit: ghc] master: Make ':info Coercible' display an arbitrary string (fixes #12390) (905dc8b) Message-ID: <20170711174226.5C7843A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/905dc8bc74bebf5370eb9237cc8756cd9fe871ae/ghc >--------------------------------------------------------------- commit 905dc8bc74bebf5370eb9237cc8756cd9fe871ae Author: Patrick Dougherty Date: Tue Jul 11 11:53:40 2017 -0400 Make ':info Coercible' display an arbitrary string (fixes #12390) This change enables the addition of an arbitrary string to the output of GHCi's ':info'. It was made for Coercible in particular but could be extended if desired. Updates haddock submodule. Test Plan: Modified test 'ghci059' to match new output. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: goldfire, rwbarton, thomie GHC Trac Issues: #12390 Differential Revision: https://phabricator.haskell.org/D3634 >--------------------------------------------------------------- 905dc8bc74bebf5370eb9237cc8756cd9fe871ae compiler/main/HscMain.hs | 3 ++- compiler/main/InteractiveEval.hs | 7 ++++--- compiler/prelude/PrelInfo.hs | 19 ++++++++++++++++++- compiler/prelude/TysWiredIn.hs | 2 +- compiler/typecheck/TcRnDriver.hs | 7 +++++-- ghc/GHCi/UI.hs | 14 ++++++++------ testsuite/tests/ghci/scripts/ghci059.stdout | 5 +++++ utils/haddock | 2 +- 8 files changed, 44 insertions(+), 15 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 905dc8bc74bebf5370eb9237cc8756cd9fe871ae From git at git.haskell.org Tue Jul 11 17:42:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 17:42:29 +0000 (UTC) Subject: [commit: ghc] master: Fix Work Balance computation in RTS stats (7c9e356) Message-ID: <20170711174229.23B7A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7c9e356de1114ab3e31f2d6d03e83672076dd533/ghc >--------------------------------------------------------------- commit 7c9e356de1114ab3e31f2d6d03e83672076dd533 Author: Douglas Wilson Date: Tue Jul 11 11:54:09 2017 -0400 Fix Work Balance computation in RTS stats An additional stat is tracked per gc: par_balanced_copied This is the the number of bytes copied by each gc thread under the balanced lmit, which is simply (copied_bytes / num_gc_threads). The stat is added to all the appropriate GC structures, so is visible in the eventlog and in GHC.Stats. A note is added explaining how work balance is computed. Remove some end of line whitespace Test Plan: ./validate experiment with the program attached to the ticket examine code changes carefully Reviewers: simonmar, austin, hvr, bgamari, erikd Reviewed By: simonmar Subscribers: Phyx, rwbarton, thomie GHC Trac Issues: #13830 Differential Revision: https://phabricator.haskell.org/D3658 >--------------------------------------------------------------- 7c9e356de1114ab3e31f2d6d03e83672076dd533 includes/RtsAPI.h | 4 ++ includes/rts/EventLogFormat.h | 3 +- libraries/base/GHC/Stats.hsc | 28 +++++++++++-- rts/RtsProbes.d | 2 +- rts/Stats.c | 97 ++++++++++++++++++++++++++++++++++++++++--- rts/Stats.h | 2 +- rts/Trace.c | 6 ++- rts/Trace.h | 22 ++++++---- rts/eventlog/EventLog.c | 13 ++++-- rts/eventlog/EventLog.h | 3 +- rts/sm/GC.c | 21 ++++++++-- 11 files changed, 172 insertions(+), 29 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 7c9e356de1114ab3e31f2d6d03e83672076dd533 From git at git.haskell.org Tue Jul 11 17:42:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 17:42:31 +0000 (UTC) Subject: [commit: ghc] master: Improve Wmissing-home-modules warning under Cabal (b0c9f34) Message-ID: <20170711174231.D4FF33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b0c9f34aa3da914524ef37294bba78afefc3ada7/ghc >--------------------------------------------------------------- commit b0c9f34aa3da914524ef37294bba78afefc3ada7 Author: Ben Gamari Date: Tue Jul 11 11:54:59 2017 -0400 Improve Wmissing-home-modules warning under Cabal Reviewers: hvr, alanz, austin Reviewed By: alanz Subscribers: rwbarton, thomie GHC Trac Issues: #13899 Differential Revision: https://phabricator.haskell.org/D3686 >--------------------------------------------------------------- b0c9f34aa3da914524ef37294bba78afefc3ada7 compiler/main/GhcMake.hs | 7 ++++++- testsuite/tests/warnings/should_compile/MissingMod.stderr | 2 +- testsuite/tests/warnings/should_compile/T13727/T13727a.stderr | 2 +- testsuite/tests/warnings/should_compile/T13727/T13727b.stderr | 2 +- testsuite/tests/warnings/should_compile/T13727/T13727f.stderr | 3 ++- testsuite/tests/warnings/should_compile/T13727/T13727g.stderr | 3 ++- testsuite/tests/warnings/should_compile/T13727/T13727h.stderr | 2 +- testsuite/tests/warnings/should_compile/T13727/T13727i.stderr | 2 +- testsuite/tests/warnings/should_compile/T13727/T13727j.stderr | 2 +- 9 files changed, 16 insertions(+), 9 deletions(-) diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs index 5935a77..4706672 100644 --- a/compiler/main/GhcMake.hs +++ b/compiler/main/GhcMake.hs @@ -195,7 +195,12 @@ warnMissingHomeModules hsc_env mod_graph = missing = map (moduleName . ms_mod) $ filter (not . is_known_module) mod_graph - msg = text "Modules are not listed in command line: " + msg + | gopt Opt_BuildingCabalPackage dflags + = text "These modules are needed for compilation but not listed in your .cabal file's other-modules: " + <> sep (map ppr missing) + | otherwise + = text "Modules are not listed in command line but needed for compilation: " <> sep (map ppr missing) warn = makeIntoWarning (Reason Opt_WarnMissingHomeModules) diff --git a/testsuite/tests/warnings/should_compile/MissingMod.stderr b/testsuite/tests/warnings/should_compile/MissingMod.stderr index 0045092..119e72c 100644 --- a/testsuite/tests/warnings/should_compile/MissingMod.stderr +++ b/testsuite/tests/warnings/should_compile/MissingMod.stderr @@ -1,5 +1,5 @@ : warning: [-Wmissing-home-modules] - Modules are not listed in command line: MissingMod1 + Modules are not listed in command line but needed for compilation: MissingMod1 [1 of 2] Compiling MissingMod1 ( MissingMod1.hs, MissingMod1.o ) [2 of 2] Compiling MissingMod ( MissingMod.hs, MissingMod.o ) diff --git a/testsuite/tests/warnings/should_compile/T13727/T13727a.stderr b/testsuite/tests/warnings/should_compile/T13727/T13727a.stderr index 64ad6d2..c77fbc4 100644 --- a/testsuite/tests/warnings/should_compile/T13727/T13727a.stderr +++ b/testsuite/tests/warnings/should_compile/T13727/T13727a.stderr @@ -1,6 +1,6 @@ : warning: [-Wmissing-home-modules] - Modules are not listed in command line: M1 + Modules are not listed in command line but needed for compilation: M1 [1 of 2] Compiling M1 ( src-lib/M1.hs, src-lib/M1.o ) [2 of 2] Compiling Main ( src-exe/Main.hs, src-exe/Main.o ) Linking src-exe/Main ... diff --git a/testsuite/tests/warnings/should_compile/T13727/T13727b.stderr b/testsuite/tests/warnings/should_compile/T13727/T13727b.stderr index 64ad6d2..c77fbc4 100644 --- a/testsuite/tests/warnings/should_compile/T13727/T13727b.stderr +++ b/testsuite/tests/warnings/should_compile/T13727/T13727b.stderr @@ -1,6 +1,6 @@ : warning: [-Wmissing-home-modules] - Modules are not listed in command line: M1 + Modules are not listed in command line but needed for compilation: M1 [1 of 2] Compiling M1 ( src-lib/M1.hs, src-lib/M1.o ) [2 of 2] Compiling Main ( src-exe/Main.hs, src-exe/Main.o ) Linking src-exe/Main ... diff --git a/testsuite/tests/warnings/should_compile/T13727/T13727f.stderr b/testsuite/tests/warnings/should_compile/T13727/T13727f.stderr index 35bfae8..20a42ba 100644 --- a/testsuite/tests/warnings/should_compile/T13727/T13727f.stderr +++ b/testsuite/tests/warnings/should_compile/T13727/T13727f.stderr @@ -1,6 +1,7 @@ : warning: [-Wmissing-home-modules] - Modules are not listed in command line: M1 Main + Modules are not listed in command line but needed for compilation: M1 + Main [1 of 3] Compiling M1 ( src-lib/M1.hs, src-lib/M1.o ) [2 of 3] Compiling Main ( src-exe/Main.hs, src-exe/Main.o ) [3 of 3] Compiling AltMain ( src-exe/AltMain.hs, src-exe/AltMain.o ) diff --git a/testsuite/tests/warnings/should_compile/T13727/T13727g.stderr b/testsuite/tests/warnings/should_compile/T13727/T13727g.stderr index 35bfae8..20a42ba 100644 --- a/testsuite/tests/warnings/should_compile/T13727/T13727g.stderr +++ b/testsuite/tests/warnings/should_compile/T13727/T13727g.stderr @@ -1,6 +1,7 @@ : warning: [-Wmissing-home-modules] - Modules are not listed in command line: M1 Main + Modules are not listed in command line but needed for compilation: M1 + Main [1 of 3] Compiling M1 ( src-lib/M1.hs, src-lib/M1.o ) [2 of 3] Compiling Main ( src-exe/Main.hs, src-exe/Main.o ) [3 of 3] Compiling AltMain ( src-exe/AltMain.hs, src-exe/AltMain.o ) diff --git a/testsuite/tests/warnings/should_compile/T13727/T13727h.stderr b/testsuite/tests/warnings/should_compile/T13727/T13727h.stderr index 1832b38..a29f764 100644 --- a/testsuite/tests/warnings/should_compile/T13727/T13727h.stderr +++ b/testsuite/tests/warnings/should_compile/T13727/T13727h.stderr @@ -1,6 +1,6 @@ : warning: [-Wmissing-home-modules] - Modules are not listed in command line: M1 + Modules are not listed in command line but needed for compilation: M1 [1 of 3] Compiling M1 ( src-lib/M1.hs, src-lib/M1.o ) [2 of 3] Compiling Main ( src-exe/Main.hs, src-exe/Main.o ) [3 of 3] Compiling AltMain ( src-exe/AltMain.hs, src-exe/AltMain.o ) diff --git a/testsuite/tests/warnings/should_compile/T13727/T13727i.stderr b/testsuite/tests/warnings/should_compile/T13727/T13727i.stderr index 1832b38..a29f764 100644 --- a/testsuite/tests/warnings/should_compile/T13727/T13727i.stderr +++ b/testsuite/tests/warnings/should_compile/T13727/T13727i.stderr @@ -1,6 +1,6 @@ : warning: [-Wmissing-home-modules] - Modules are not listed in command line: M1 + Modules are not listed in command line but needed for compilation: M1 [1 of 3] Compiling M1 ( src-lib/M1.hs, src-lib/M1.o ) [2 of 3] Compiling Main ( src-exe/Main.hs, src-exe/Main.o ) [3 of 3] Compiling AltMain ( src-exe/AltMain.hs, src-exe/AltMain.o ) diff --git a/testsuite/tests/warnings/should_compile/T13727/T13727j.stderr b/testsuite/tests/warnings/should_compile/T13727/T13727j.stderr index f6d3197..e85f778 100644 --- a/testsuite/tests/warnings/should_compile/T13727/T13727j.stderr +++ b/testsuite/tests/warnings/should_compile/T13727/T13727j.stderr @@ -1,6 +1,6 @@ : warning: [-Wmissing-home-modules] - Modules are not listed in command line: Main + Modules are not listed in command line but needed for compilation: Main [1 of 3] Compiling M1 ( src-lib/M1.hs, src-lib/M1.o ) [2 of 3] Compiling Main ( src-exe/Main.hs, src-exe/Main.o ) [3 of 3] Compiling AltMain ( src-exe/AltMain.hs, src-exe/AltMain.o ) From git at git.haskell.org Tue Jul 11 17:42:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 17:42:35 +0000 (UTC) Subject: [commit: ghc] master: Add testcase for T13818 (6cff2ca) Message-ID: <20170711174235.3518E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6cff2caddd9b329272a7d6965b20432e8078e0d8/ghc >--------------------------------------------------------------- commit 6cff2caddd9b329272a7d6965b20432e8078e0d8 Author: Douglas Wilson Date: Tue Jul 11 11:55:15 2017 -0400 Add testcase for T13818 Annotations currently fail to type check if they annotation cannot be loaded into ghci, such as when built with -fno-code. Test Plan: ./validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13818 Differential Revision: https://phabricator.haskell.org/D3701 >--------------------------------------------------------------- 6cff2caddd9b329272a7d6965b20432e8078e0d8 .../T4491 => annotations/should_compile/T13818}/A.hs | 7 +++---- .../T9562/B.hs-boot => annotations/should_compile/T13818/B.hs} | 2 +- testsuite/tests/annotations/should_compile/T13818/all.T | 1 + 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/testsuite/tests/quasiquotation/T4491/A.hs b/testsuite/tests/annotations/should_compile/T13818/A.hs similarity index 62% copy from testsuite/tests/quasiquotation/T4491/A.hs copy to testsuite/tests/annotations/should_compile/T13818/A.hs index dad3d03..1f04845 100644 --- a/testsuite/tests/quasiquotation/T4491/A.hs +++ b/testsuite/tests/annotations/should_compile/T13818/A.hs @@ -1,9 +1,8 @@ {-# LANGUAGE DeriveDataTypeable #-} - module A where -import Data.Data import Data.Typeable +import Data.Data -data Foo = Foo Int - deriving (Show, Data, Typeable) +data FromA = FromA + deriving (Typeable, Data) diff --git a/testsuite/tests/driver/T9562/B.hs-boot b/testsuite/tests/annotations/should_compile/T13818/B.hs similarity index 50% copy from testsuite/tests/driver/T9562/B.hs-boot copy to testsuite/tests/annotations/should_compile/T13818/B.hs index facbc8c..d64afef 100644 --- a/testsuite/tests/driver/T9562/B.hs-boot +++ b/testsuite/tests/annotations/should_compile/T13818/B.hs @@ -2,4 +2,4 @@ module B where import A -oops :: F a b -> a -> b +{-# ANN module FromA #-} diff --git a/testsuite/tests/annotations/should_compile/T13818/all.T b/testsuite/tests/annotations/should_compile/T13818/all.T new file mode 100644 index 0000000..ce858b6 --- /dev/null +++ b/testsuite/tests/annotations/should_compile/T13818/all.T @@ -0,0 +1 @@ +test('T13818', [expect_broken(13818),req_interp, omit_ways(prof_ways), extra_files(['A.hs', 'B.hs'])], multimod_compile, ['B', '-v0 -fno-code']) \ No newline at end of file From git at git.haskell.org Tue Jul 11 17:42:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 17:42:37 +0000 (UTC) Subject: [commit: ghc] master: users-guide/rel-notes: Describe #13875 fix (ccb849f) Message-ID: <20170711174237.E29343A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ccb849f8ea39582d2cfc5c045abe9768992dccb6/ghc >--------------------------------------------------------------- commit ccb849f8ea39582d2cfc5c045abe9768992dccb6 Author: Ben Gamari Date: Tue Jul 11 12:01:05 2017 -0400 users-guide/rel-notes: Describe #13875 fix Test Plan: Read it. Reviewers: simonmar, austin Reviewed By: simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13875 Differential Revision: https://phabricator.haskell.org/D3710 >--------------------------------------------------------------- ccb849f8ea39582d2cfc5c045abe9768992dccb6 docs/users_guide/8.2.1-notes.rst | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index ba17e35..9dccc33 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -38,6 +38,12 @@ Compiler - TODO FIXME. +- A bug in the :ghc-flag:`-XApplicativeDo` extension resulting in strict pattern + matches to be performed lazily (:ghc-ticket:`13875`) has been fixed. Note that + this means some programs which previously typechecked under ``ApplicativeDo`` + will no longer as it is not possible to implement strict pattern matching + using only ``Applicative``. + - Old profiling flags ``-auto-all``, ``-auto``, and ``-caf-all`` are deprecated and their usage provokes a compile-time warning. From git at git.haskell.org Tue Jul 11 17:42:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 17:42:40 +0000 (UTC) Subject: [commit: ghc] master: Always allow -staticlib (b8f33bc) Message-ID: <20170711174240.9D10E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b8f33bc6b738b0378976e42b79369f0e53b680c7/ghc >--------------------------------------------------------------- commit b8f33bc6b738b0378976e42b79369f0e53b680c7 Author: Moritz Angermann Date: Tue Jul 11 11:57:48 2017 -0400 Always allow -staticlib the `-staticlib` flag is currently only supported on apple platforms, due to the avaiablity of libtool (the apple version, which is unlike the gnu version). This however prevents the use of -staticlib in cases where it would be beneficial as well. The functionality that `-staticlib` uses from `libtool` can be stubbed with a small script like the following: ``` #!/bin/bash # This script pretends to be libtool. And supports # only a limited set of flags. # # It is supposed to be a stand in for libtool -static, whic # creates a static archive. This is done by locating all -l # libs in the provied -L library paths, and building an # MRI script to create the final archive from all the libraries, and # other provided inputs. # name=${0##*/} target=${name%-*} set -e ldflags_L=() ldflags_l=() output="" inputs=() STATIC=0 DYNAMIC=1 mode=$DYNAMIC verbose=0 # find_lib path path path path function find_lib () { lib=$1; shift 1; for dir in $@; do if [ -f "$dir/$lib" ]; then echo "$dir/$lib" break fi done } while [ "$#" -gt 0 ]; do case "$1" in -v|--verbose) verbose=1; shift 1;; -o) output="$2"; shift 2;; -L*) ldflags_L+=("${1:2:${#1}-2}"); shift 1;; -l*) ldflags_l+=("lib${1:2:${#1}-2}.a"); shift 1;; -static) mode=$STATIC; shift 1;; -dynamic) mode=$DYNAMIC; shift 1;; -Wl,*) ldflags+=("${1#*,}"); shift 1;; -*) echo "unknown option: $1" >&2; exit 1;; *) inputs+=("$1"); shift 1;; esac done if [ ! $mode == $STATIC ]; then echo "-dynamic not supported!" >&2; exit 1; fi MRI="create ${output}\n" for input in "${ldflags_l[@]}"; do lib=$(find_lib $input ${ldflags_L[@]}) if [ -z $lib ]; then echo "Failed to find lib $input" >&2 exit 1 else MRI+="addlib $lib\n" continue fi done for input in "${inputs[@]}"; do MRI+="addmod $input\n" done MRI+="save\nend\n" echo -e "$MRI" | $target-ar -M $target-ranlib $output ``` if `ar` supports MRI scripts. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3706 >--------------------------------------------------------------- b8f33bc6b738b0378976e42b79369f0e53b680c7 compiler/main/DriverPipeline.hs | 5 +---- docs/users_guide/phases.rst | 8 +++----- utils/mkUserGuidePart/Options/Linking.hs | 7 ++++--- 3 files changed, 8 insertions(+), 12 deletions(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index eed66b2..ad0e0c8 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -2082,10 +2082,7 @@ linkDynLibCheck dflags o_files dep_packages linkStaticLibCheck :: DynFlags -> [String] -> [InstalledUnitId] -> IO () linkStaticLibCheck dflags o_files dep_packages - = do - when (platformOS (targetPlatform dflags) `notElem` [OSiOS, OSDarwin]) $ - throwGhcExceptionIO (ProgramError "Static archive creation only supported on Darwin/OS X/iOS") - linkBinary' True dflags o_files dep_packages + = linkBinary' True dflags o_files dep_packages -- ----------------------------------------------------------------------------- -- Running CPP diff --git a/docs/users_guide/phases.rst b/docs/users_guide/phases.rst index 1efe6a4..f35ba1b 100644 --- a/docs/users_guide/phases.rst +++ b/docs/users_guide/phases.rst @@ -539,11 +539,9 @@ for example). .. ghc-flag:: -staticlib - On Darwin/OS X/iOS only, link all passed files into a static library - suitable for linking into an iOS (when using a cross-compiler) or - Mac Xcode project. To control the name, use the :ghc-flag:`-o` ⟨name⟩ option - as usual. The default name is ``liba.a``. This should nearly always - be passed when compiling for iOS with a cross-compiler. + Link all passed files into a static library suitable for linking. + To control the name, use the :ghc-flag:`-o` ⟨name⟩ option + as usual. The default name is ``liba.a``. .. ghc-flag:: -L ⟨dir⟩ diff --git a/utils/mkUserGuidePart/Options/Linking.hs b/utils/mkUserGuidePart/Options/Linking.hs index 9edc7c3..3142020 100644 --- a/utils/mkUserGuidePart/Options/Linking.hs +++ b/utils/mkUserGuidePart/Options/Linking.hs @@ -11,9 +11,10 @@ linkingOptions = } , flag { flagName = "-staticlib" , flagDescription = - "On Darwin/OS X/iOS only, generate a standalone static library " ++ - "(as opposed to an executable). This is the usual way to " ++ - "compile for iOS." + "Generate a standalone static library (as opposed to an " ++ + "executable). This is useful when cross compiling. The " ++ + "library together with all its dependencies ends up in in a " ++ + "single static library that can be linked against." , flagType = DynamicFlag } , flag { flagName = "-fPIC" From git at git.haskell.org Tue Jul 11 17:42:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 17:42:44 +0000 (UTC) Subject: [commit: ghc] master: Suppress unused warnings for selectors for some derived classes (15fcd9a) Message-ID: <20170711174244.8A2213A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/15fcd9adb75b95b32fbe08d066a2ada5f298d667/ghc >--------------------------------------------------------------- commit 15fcd9adb75b95b32fbe08d066a2ada5f298d667 Author: Ryan Scott Date: Tue Jul 11 11:57:05 2017 -0400 Suppress unused warnings for selectors for some derived classes Although derived `Read`, `Show`, and `Generic` instances technically don't //use// the record selectors of the data type for which an instance is being derived, the derived code is affected by the //presence// of record selectors. As a result, we should suppress `-Wunused-binds` for those record selectors when deriving these classes. This is accomplished by threading through more information from `hasStockDeriving`. Test Plan: make test TEST=T13919 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13919 Differential Revision: https://phabricator.haskell.org/D3704 >--------------------------------------------------------------- 15fcd9adb75b95b32fbe08d066a2ada5f298d667 compiler/typecheck/TcDeriv.hs | 39 ++++----- compiler/typecheck/TcDerivUtils.hs | 92 +++++++++++++++++----- testsuite/tests/deriving/should_compile/T13919.hs | 13 +++ .../tests/deriving/should_compile/T13919.stderr | 4 +- testsuite/tests/deriving/should_compile/all.T | 1 + 5 files changed, 110 insertions(+), 39 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 15fcd9adb75b95b32fbe08d066a2ada5f298d667 From git at git.haskell.org Tue Jul 11 17:42:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 17:42:47 +0000 (UTC) Subject: [commit: ghc] master: ByteCodeGen: use depth instead of offsets in BCEnv (fe6618b) Message-ID: <20170711174247.416D13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fe6618b14712b829b8675fc6024dd33e9598d09a/ghc >--------------------------------------------------------------- commit fe6618b14712b829b8675fc6024dd33e9598d09a Author: Michal Terepeta Date: Tue Jul 11 12:00:16 2017 -0400 ByteCodeGen: use depth instead of offsets in BCEnv This is based on unfinished work in D38 started by Simon Marlow and is the first step for fixing #13825. (next step use byte-indexing for stack) The change boils down to adjusting everything in BCEnv by +1, which simplifies the code a bit. I've also looked into a weird stack adjustement that we did in `getIdValFromApStack` and moved it to `ByteCodeGen` to just keep everything in one place. I've left a comment about this. Signed-off-by: Michal Terepeta Test Plan: ./validate Reviewers: austin, hvr, bgamari, simonmar Reviewed By: bgamari, simonmar Subscribers: simonmar, rwbarton, thomie GHC Trac Issues: #13825 Differential Revision: https://phabricator.haskell.org/D3708 >--------------------------------------------------------------- fe6618b14712b829b8675fc6024dd33e9598d09a compiler/ghci/ByteCodeGen.hs | 60 +++++++++++++++++++++++--------------------- libraries/ghci/GHCi/Run.hs | 4 +-- 2 files changed, 32 insertions(+), 32 deletions(-) diff --git a/compiler/ghci/ByteCodeGen.hs b/compiler/ghci/ByteCodeGen.hs index a7cd6da..5c236f3 100644 --- a/compiler/ghci/ByteCodeGen.hs +++ b/compiler/ghci/ByteCodeGen.hs @@ -211,8 +211,8 @@ type BCInstrList = OrdList BCInstr type Sequel = Word -- back off to this depth before ENTER --- Maps Ids to the offset from the stack _base_ so we don't have --- to mess with it after each push/pop. +-- | Maps Ids to their stack depth. This allows us to avoid having to mess with +-- it after each push/pop. type BCEnv = Map Id Word -- To find vars on the stack {- @@ -403,13 +403,20 @@ schemeER_wrk d p rhs | otherwise = schemeE (fromIntegral d) 0 p rhs getVarOffSets :: Word -> BCEnv -> [Id] -> [(Id, Word16)] -getVarOffSets d p = catMaybes . map (getOffSet d p) - -getOffSet :: Word -> BCEnv -> Id -> Maybe (Id, Word16) -getOffSet d env id - = case lookupBCEnv_maybe id env of +getVarOffSets depth env = catMaybes . map getOffSet + where + getOffSet id = case lookupBCEnv_maybe id env of Nothing -> Nothing - Just offset -> Just (id, trunc16 $ d - offset) + Just offset -> + -- michalt: I'm not entirely sure why we need the stack + -- adjustement by 2 here. I initially thought that there's + -- something off with getIdValFromApStack (the only user of this + -- value), but it looks ok to me. My current hypothesis is that + -- this "adjustement" is needed due to stack manipulation for + -- BRK_FUN in Interpreter.c In any case, this is used only when + -- we trigger a breakpoint. + let adjustement = 2 + in Just (id, trunc16 $ depth - offset + adjustement) trunc16 :: Word -> Word16 trunc16 w @@ -471,7 +478,8 @@ schemeE d s p (AnnLet (AnnNonRec x (_,rhs)) (_,body)) -- saturated constructor application. -- Just allocate the constructor and carry on alloc_code <- mkConAppCode d s p data_con args_r_to_l - body_code <- schemeE (d+1) s (Map.insert x d p) body + let !d2 = d + 1 + body_code <- schemeE d2 s (Map.insert x d2 p) body return (alloc_code `appOL` body_code) -- General case for let. Generates correct, if inefficient, code in @@ -861,10 +869,9 @@ doCase d s p (_,scrut) bndr alts is_unboxed_tuple -- Env in which to compile the alts, not including -- any vars bound by the alts themselves - d_bndr' = fromIntegral d_bndr - 1 - p_alts0 = Map.insert bndr d_bndr' p + p_alts0 = Map.insert bndr d_bndr p p_alts = case is_unboxed_tuple of - Just ubx_bndr -> Map.insert ubx_bndr d_bndr' p_alts0 + Just ubx_bndr -> Map.insert ubx_bndr d_bndr p_alts0 Nothing -> p_alts0 bndr_ty = idType bndr @@ -947,7 +954,7 @@ doCase d s p (_,scrut) bndr alts is_unboxed_tuple rel_slots = nub $ map fromIntegral $ concat (map spread binds) spread (id, offset) | isFollowableArg (bcIdArgRep id) = [ rel_offset ] | otherwise = [] - where rel_offset = trunc16 $ d - fromIntegral offset - 1 + where rel_offset = trunc16 $ d - fromIntegral offset alt_stuff <- mapM codeAlt alts alt_final <- mkMultiBranch maybe_ncons alt_stuff @@ -1377,18 +1384,14 @@ pushAtom d p (AnnVar v) = do dflags <- getDynFlags let sz :: Word16 sz = fromIntegral (idSizeW dflags v) - l = trunc16 $ d - d_v + fromIntegral sz - 2 + l = trunc16 $ d - d_v + fromIntegral sz - 1 return (toOL (genericReplicate sz (PUSH_L l)), sz) - -- d - d_v the number of words between the TOS - -- and the 1st slot of the object - -- - -- d - d_v - 1 the offset from the TOS of the 1st slot - -- - -- d - d_v - 1 + sz - 1 the offset from the TOS of the last slot - -- of the object. - -- - -- Having found the last slot, we proceed to copy the right number of - -- slots on to the top of the stack. + -- d - d_v offset from TOS to the first slot of the object + -- + -- d - d_v + sz - 1 offset from the TOS of the last slot of the object + -- + -- Having found the last slot, we proceed to copy the right number of + -- slots on to the top of the stack. | otherwise -- v must be a global variable = do topStrings <- getTopStrings @@ -1676,12 +1679,11 @@ atomRep e = toArgRep (atomPrimRep e) isPtrAtom :: AnnExpr' Id ann -> Bool isPtrAtom e = isFollowableArg (atomRep e) --- Let szsw be the sizes in words of some items pushed onto the stack, --- which has initial depth d'. Return the values which the stack environment --- should map these items to. +-- | Let szsw be the sizes in words of some items pushed onto the stack, which +-- has initial depth @original_depth at . Return the values which the stack +-- environment should map these items to. mkStackOffsets :: Word -> [Word] -> [Word] -mkStackOffsets original_depth szsw - = map (subtract 1) (tail (scanl (+) original_depth szsw)) +mkStackOffsets original_depth szsw = tail (scanl' (+) original_depth szsw) typeArgRep :: Type -> ArgRep typeArgRep = toArgRep . typePrimRep1 diff --git a/libraries/ghci/GHCi/Run.hs b/libraries/ghci/GHCi/Run.hs index eecafa1..d058775 100644 --- a/libraries/ghci/GHCi/Run.hs +++ b/libraries/ghci/GHCi/Run.hs @@ -344,9 +344,7 @@ mkCostCentres _ _ = return [] getIdValFromApStack :: HValue -> Int -> IO (Maybe HValue) getIdValFromApStack apStack (I# stackDepth) = do - case getApStackVal# apStack (stackDepth +# 1#) of - -- The +1 is magic! I don't know where it comes - -- from, but this makes things line up. --SDM + case getApStackVal# apStack stackDepth of (# ok, result #) -> case ok of 0# -> return Nothing -- AP_STACK not found From git at git.haskell.org Tue Jul 11 17:42:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 17:42:49 +0000 (UTC) Subject: [commit: ghc] master: Sort list of failed tests for easier comparison between runs (cb8db9b) Message-ID: <20170711174249.F1D483A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cb8db9bcbdbe5008fbefb3ce262a8f06fb7366da/ghc >--------------------------------------------------------------- commit cb8db9bcbdbe5008fbefb3ce262a8f06fb7366da Author: Andreas Klebinger Date: Tue Jul 11 11:57:39 2017 -0400 Sort list of failed tests for easier comparison between runs Test Plan: Running the testsuite. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13922 Differential Revision: https://phabricator.haskell.org/D3705 >--------------------------------------------------------------- cb8db9bcbdbe5008fbefb3ce262a8f06fb7366da testsuite/driver/testlib.py | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index b730685..4212214 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -2054,7 +2054,7 @@ def printUnexpectedTests(file, testInfoss): if not name.endswith('.T')) if unexpected: file.write('Unexpected results from:\n') - file.write('TEST="' + ' '.join(unexpected) + '"\n') + file.write('TEST="' + ' '.join(sorted(unexpected)) + '"\n') file.write('\n') def printTestInfosSummary(file, testInfos): From git at git.haskell.org Tue Jul 11 18:10:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 18:10:22 +0000 (UTC) Subject: [commit: ghc] master: Add Template Haskell support for overloaded labels (81de42c) Message-ID: <20170711181022.7A7AC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/81de42cb589540666a365808318589211924f9cd/ghc >--------------------------------------------------------------- commit 81de42cb589540666a365808318589211924f9cd Author: Matthew Pickering Date: Tue Jul 11 19:01:31 2017 +0100 Add Template Haskell support for overloaded labels Reviewers: RyanGlScott, austin, goldfire, bgamari Reviewed By: RyanGlScott, goldfire, bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3715 >--------------------------------------------------------------- 81de42cb589540666a365808318589211924f9cd compiler/deSugar/DsMeta.hs | 8 +++++++- compiler/hsSyn/Convert.hs | 1 + compiler/prelude/THNames.hs | 8 ++++++-- .../template-haskell/Language/Haskell/TH/Lib.hs | 5 ++++- .../template-haskell/Language/Haskell/TH/Ppr.hs | 1 + .../template-haskell/Language/Haskell/TH/Syntax.hs | 1 + libraries/template-haskell/changelog.md | 2 ++ testsuite/tests/th/TH_overloadedlabels.hs | 21 +++++++++++++++++++++ testsuite/tests/th/all.T | 1 + 9 files changed, 44 insertions(+), 4 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 81de42cb589540666a365808318589211924f9cd From git at git.haskell.org Tue Jul 11 18:36:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 18:36:25 +0000 (UTC) Subject: [commit: ghc] master: Fix logic error in GhcMake.enableCodeGenForTH (ea75124) Message-ID: <20170711183625.A4BE03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ea751248d80efe7633a31120da56e9a31b6820ff/ghc >--------------------------------------------------------------- commit ea751248d80efe7633a31120da56e9a31b6820ff Author: Douglas Wilson Date: Tue Jul 11 13:58:17 2017 -0400 Fix logic error in GhcMake.enableCodeGenForTH transitive_deps_set was incorrect, it was not considering the dependencies of dependencies in some cases. I've corrected it and tidied it up a little. The test case from leftaroundabout, as linked to from the ticket, is added with small modifications to flatten directory structure. Test Plan: make test TEST=T13949 Reviewers: austin, bgamari, alexbiehl Reviewed By: alexbiehl Subscribers: rwbarton, thomie, alexbiehl GHC Trac Issues: #13949 Differential Revision: https://phabricator.haskell.org/D3720 >--------------------------------------------------------------- ea751248d80efe7633a31120da56e9a31b6820ff compiler/main/GhcMake.hs | 37 ++++++++++++---------- testsuite/tests/th/should_compile/T13949/ASCII.hs | 10 ++++++ .../T12062 => th/should_compile/T13949}/Makefile | 0 .../th/should_compile/T13949/PatternGenerator.hs | 8 +++++ testsuite/tests/th/should_compile/T13949/These.hs | 4 +++ testsuite/tests/th/should_compile/T13949/Tree.hs | 6 ++++ testsuite/tests/th/should_compile/T13949/all.T | 2 ++ 7 files changed, 51 insertions(+), 16 deletions(-) diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs index 4706672..f4ea4de 100644 --- a/compiler/main/GhcMake.hs +++ b/compiler/main/GhcMake.hs @@ -1994,27 +1994,32 @@ enableCodeGenForTH target nodemap = , ms_hspp_opts = updOptLevel 0 $ dflags {hscTarget = target} } | otherwise = return ms - needs_codegen_set = transitive_deps_set Set.empty th_modSums - th_modSums = + + needs_codegen_set = transitive_deps_set [ ms | mss <- Map.elems nodemap , Right ms <- mss , needsTemplateHaskellOrQQ $ [ms] ] - transitive_deps_set marked_mods modSums = foldl' go marked_mods modSums - go marked_mods ms - | Set.member (ms_mod ms) marked_mods = marked_mods - | otherwise = - let deps = - [ dep_ms - | (L _ mn, NotBoot) <- msDeps ms - , dep_ms <- - toList (Map.lookup (mn, NotBoot) nodemap) >>= toList >>= - toList - ] - new_marked_mods = - marked_mods `Set.union` Set.fromList (fmap ms_mod deps) - in transitive_deps_set new_marked_mods deps + + -- find the set of all transitive dependencies of a list of modules. + transitive_deps_set modSums = foldl' go Set.empty modSums + where + go marked_mods ms at ModSummary{ms_mod} + | ms_mod `Set.member` marked_mods = marked_mods + | otherwise = + let deps = + [ dep_ms + -- If a module imports a boot module, msDeps helpfully adds a + -- dependency to that non-boot module in it's result. This + -- means we don't have to think about boot modules here. + | (L _ mn, NotBoot) <- msDeps ms + , dep_ms <- + toList (Map.lookup (mn, NotBoot) nodemap) >>= toList >>= + toList + ] + new_marked_mods = Set.insert ms_mod marked_mods + in foldl' go new_marked_mods deps mkRootMap :: [ModSummary] -> NodeMap [Either ErrMsg ModSummary] mkRootMap summaries = Map.insertListWith (flip (++)) diff --git a/testsuite/tests/th/should_compile/T13949/ASCII.hs b/testsuite/tests/th/should_compile/T13949/ASCII.hs new file mode 100644 index 0000000..4539987 --- /dev/null +++ b/testsuite/tests/th/should_compile/T13949/ASCII.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} + +module ASCII () where + +import Tree +import PatternGenerator + +type EP g = Bool + +templateFoo ''EP ['A'..'Z'] diff --git a/testsuite/tests/driver/T12062/Makefile b/testsuite/tests/th/should_compile/T13949/Makefile similarity index 100% copy from testsuite/tests/driver/T12062/Makefile copy to testsuite/tests/th/should_compile/T13949/Makefile diff --git a/testsuite/tests/th/should_compile/T13949/PatternGenerator.hs b/testsuite/tests/th/should_compile/T13949/PatternGenerator.hs new file mode 100644 index 0000000..2805650 --- /dev/null +++ b/testsuite/tests/th/should_compile/T13949/PatternGenerator.hs @@ -0,0 +1,8 @@ +module PatternGenerator where + +import Tree + +import Language.Haskell.TH + +templateFoo :: Name -> [Char] -> DecsQ +templateFoo _ _ = return [] diff --git a/testsuite/tests/th/should_compile/T13949/These.hs b/testsuite/tests/th/should_compile/T13949/These.hs new file mode 100644 index 0000000..eefe506 --- /dev/null +++ b/testsuite/tests/th/should_compile/T13949/These.hs @@ -0,0 +1,4 @@ +module These where + +tuc :: t (k, a) +tuc = undefined diff --git a/testsuite/tests/th/should_compile/T13949/Tree.hs b/testsuite/tests/th/should_compile/T13949/Tree.hs new file mode 100644 index 0000000..d6fdc0c --- /dev/null +++ b/testsuite/tests/th/should_compile/T13949/Tree.hs @@ -0,0 +1,6 @@ +module Tree where + +import These + +mp :: Maybe (Int, ()) +mp = tuc diff --git a/testsuite/tests/th/should_compile/T13949/all.T b/testsuite/tests/th/should_compile/T13949/all.T new file mode 100644 index 0000000..9975e58 --- /dev/null +++ b/testsuite/tests/th/should_compile/T13949/all.T @@ -0,0 +1,2 @@ +test('T13949', extra_files(['ASCII.hs', 'PatternGenerator.hs', 'These.hs', 'Tree.hs']), + multimod_compile, ['ASCII PatternGenerator These Tree', '-fno-code -v0']) \ No newline at end of file From git at git.haskell.org Tue Jul 11 18:36:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 18:36:28 +0000 (UTC) Subject: [commit: ghc] master: Optimize TimerManager (abda03b) Message-ID: <20170711183628.655653A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/abda03be6794ffd9bbc2c4f77d7f9d534a202b21/ghc >--------------------------------------------------------------- commit abda03be6794ffd9bbc2c4f77d7f9d534a202b21 Author: alexbiehl Date: Tue Jul 11 13:57:51 2017 -0400 Optimize TimerManager After discussion with Kazu Yamamoto we decided to try two things: - replace current finger tree based priority queue through a radix tree based one (code is based on IntPSQ from the psqueues package) - after editing the timer queue: don't wake up the timer manager if the next scheduled time didn't change Benchmark results (number of TimerManager-Operations measured over 20 seconds, 5 runs each, higher is better) ``` -- baseline (timermanager action commented out) 28817088 28754681 27230541 27267441 28828815 -- ghc-8.3 with wake opt and new timer queue 18085502 17892831 18005256 18791301 17912456 -- ghc-8.3 with old timer queue 6982155 7003572 6834625 6979634 6664339 ``` Here is the benchmark code: ``` {-# LANGUAGE BangPatterns #-} module Main where import Control.Monad import Control.Monad.IO.Class import Control.Monad.Trans.State.Strict import Data.Foldable import GHC.Event import System.Random import Control.Concurrent import Control.Exception import Data.IORef main :: IO () main = do let seed = 12345 :: Int nthreads = 1 :: Int benchTime = 20 :: Int -- in seconds timerManager <- getSystemTimerManager :: IO TimerManager let {- worker loop depending on the random generator it either * registers a new timeout * updates existing timeout * or cancels an existing timeout Additionally it keeps track of a counter tracking how often a timermanager was being modified. -} loop :: IORef Int -> [TimeoutKey] -> StdGen -> IO a loop !i !timeouts !rng = do let (rand0, rng') = next rng (rand1, rng'') = next rng' case rand0 `mod` 3 of 0 -> do timeout <- registerTimeout timerManager (rand1) (return ()) modifyIORef' i (+1) loop i (timeout:timeouts) rng'' 1 | (timeout:_) <- timeouts -> do updateTimeout timerManager timeout (rand1) modifyIORef' i (+1) loop i timeouts rng'' | otherwise -> loop i timeouts rng' 2 | (timeout:timeouts') <- timeouts -> do unregisterTimeout timerManager timeout modifyIORef' i (+1) loop i timeouts' rng' | otherwise -> loop i timeouts rng' _ -> loop i timeouts rng' let -- run a computation which can produce new -- random generators on demand withRng m = evalStateT m (mkStdGen seed) -- split a new random generator newRng = do (rng1, rng2) <- split <$> get put rng1 return rng2 counters <- withRng $ do replicateM nthreads $ do rng <- newRng ref <- liftIO (newIORef 0) liftIO $ forkIO (loop ref [] rng) return ref threadDelay (1000000 * benchTime) for_ counters $ \ref -> do n <- readIORef ref putStrLn (show n) ``` Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: Phyx, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3707 >--------------------------------------------------------------- abda03be6794ffd9bbc2c4f77d7f9d534a202b21 libraries/base/GHC/Event/PSQ.hs | 808 +++++++++++++++---------------- libraries/base/GHC/Event/TimerManager.hs | 21 +- 2 files changed, 404 insertions(+), 425 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 abda03be6794ffd9bbc2c4f77d7f9d534a202b21 From git at git.haskell.org Tue Jul 11 18:36:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 18:36:31 +0000 (UTC) Subject: [commit: ghc] master: Fix #13948 by being pickier about when to suggest DataKinds (ba46e63) Message-ID: <20170711183631.2EF543A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ba46e63f3d6f7d0438a0262f6711f8a219c703bc/ghc >--------------------------------------------------------------- commit ba46e63f3d6f7d0438a0262f6711f8a219c703bc Author: Ryan Scott Date: Tue Jul 11 13:59:07 2017 -0400 Fix #13948 by being pickier about when to suggest DataKinds Commit 343cb32d0983f576d344a2d04a35c3fd6eecf2c5 (#13568) made GHC a bit too cavalier in suggesting when data constructors are in scope (and suggesting the use of `DataKinds`). This tones down the suggestions so that `DataKinds` is only suggested if a data constructor of that name is actually in scope (previously, it would always suggest, even if it was out of scope). Fixes #13948. Test Plan: ./validate Reviewers: mpickering, austin, bgamari Reviewed By: mpickering Subscribers: rwbarton, thomie GHC Trac Issues: #13948 Differential Revision: https://phabricator.haskell.org/D3719 >--------------------------------------------------------------- ba46e63f3d6f7d0438a0262f6711f8a219c703bc compiler/rename/RnEnv.hs | 11 ++++++++++- 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 +--- testsuite/tests/parser/should_fail/readFail001.stderr | 1 - testsuite/tests/rename/prog003/rename.prog003.stderr | 4 +--- testsuite/tests/rename/should_fail/T1595a.stderr | 1 - testsuite/tests/rename/should_fail/T5745.stderr | 4 +--- testsuite/tests/typecheck/should_fail/T1595.stderr | 2 -- testsuite/tests/typecheck/should_fail/tcfail048.stderr | 1 - testsuite/tests/typecheck/should_fail/tcfail053.stderr | 1 - 14 files changed, 15 insertions(+), 25 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ba46e63f3d6f7d0438a0262f6711f8a219c703bc From git at git.haskell.org Tue Jul 11 18:36:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 18:36:34 +0000 (UTC) Subject: [commit: ghc] master: Fix #13947 by checking for unbounded names more (85ac65c) Message-ID: <20170711183634.520B83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/85ac65c5f0b057f1b07ed7bf9a8d9aeae4ce1390/ghc >--------------------------------------------------------------- commit 85ac65c5f0b057f1b07ed7bf9a8d9aeae4ce1390 Author: Ryan Scott Date: Tue Jul 11 13:59:29 2017 -0400 Fix #13947 by checking for unbounded names more Commit 2484d4dae65c81f218dcfe494b963b2630bb8fa6 accidentally dropped a call to `isUnboundName` in an important location. This re-adds it. Fixes #13947. Test Plan: make test TEST=T13947 Reviewers: adamgundry, austin, bgamari Reviewed By: adamgundry Subscribers: rwbarton, thomie GHC Trac Issues: #13947 Differential Revision: https://phabricator.haskell.org/D3718 >--------------------------------------------------------------- 85ac65c5f0b057f1b07ed7bf9a8d9aeae4ce1390 compiler/rename/RnTypes.hs | 5 +++-- testsuite/tests/rename/should_fail/T13947.hs | 5 +++++ testsuite/tests/rename/should_fail/T13947.stderr | 3 +++ testsuite/tests/rename/should_fail/all.T | 1 + 4 files changed, 12 insertions(+), 2 deletions(-) diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs index 35b67a2..014d485 100644 --- a/compiler/rename/RnTypes.hs +++ b/compiler/rename/RnTypes.hs @@ -1431,8 +1431,9 @@ sectionPrecErr op@(n1,_) arg_op@(n2,_) section nest 4 (text "in the section:" <+> quotes (ppr section))] is_unbound :: OpName -> Bool -is_unbound UnboundOp{} = True -is_unbound _ = False +is_unbound (NormalOp n) = isUnboundName n +is_unbound UnboundOp{} = True +is_unbound _ = False ppr_opfix :: (OpName, Fixity) -> SDoc ppr_opfix (op, fixity) = pp_op <+> brackets (ppr fixity) diff --git a/testsuite/tests/rename/should_fail/T13947.hs b/testsuite/tests/rename/should_fail/T13947.hs new file mode 100644 index 0000000..bc435e7 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T13947.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE TypeOperators #-} +module T13947 where + +f :: () -> Int :~: Int +f = undefined diff --git a/testsuite/tests/rename/should_fail/T13947.stderr b/testsuite/tests/rename/should_fail/T13947.stderr new file mode 100644 index 0000000..8a636a2 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T13947.stderr @@ -0,0 +1,3 @@ + +T13947.hs:4:12: error: + Not in scope: type constructor or class ‘:~:’ diff --git a/testsuite/tests/rename/should_fail/all.T b/testsuite/tests/rename/should_fail/all.T index 457f401..f7f7719 100644 --- a/testsuite/tests/rename/should_fail/all.T +++ b/testsuite/tests/rename/should_fail/all.T @@ -127,3 +127,4 @@ test('T11592', normal, compile_fail, ['']) test('T12879', normal, compile_fail, ['']) test('T13644', expect_broken(13644), multimod_compile_fail, ['T13644','-v0']) test('T13568', normal, multimod_compile_fail, ['T13568','-v0']) +test('T13947', normal, compile_fail, ['']) From git at git.haskell.org Tue Jul 11 18:36:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 18:36:37 +0000 (UTC) Subject: [commit: ghc] master: Remove unnecessarily returned res_ty from rejigConRes (a249e93) Message-ID: <20170711183637.0FF4E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a249e9398d49882fdcb1575bba99e2dc12ddedd9/ghc >--------------------------------------------------------------- commit a249e9398d49882fdcb1575bba99e2dc12ddedd9 Author: Ryan Scott Date: Tue Jul 11 14:03:13 2017 -0400 Remove unnecessarily returned res_ty from rejigConRes @goldfire noticed that we don't need to thread through `res_ty` through to the return type of `rejigConRes`, as it never changes. Reviewers: goldfire, austin, bgamari Reviewed By: goldfire Subscribers: rwbarton, thomie, goldfire Differential Revision: https://phabricator.haskell.org/D3725 >--------------------------------------------------------------- a249e9398d49882fdcb1575bba99e2dc12ddedd9 compiler/typecheck/TcTyClsDecls.hs | 21 ++++++++++----------- 1 file changed, 10 insertions(+), 11 deletions(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 7400483..b0f39d3 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1586,10 +1586,10 @@ tcConDecl rep_tycon tmpl_bndrs res_tmpl ; ctxt <- zonkTcTypeToTypes ze ctxt ; res_ty <- zonkTcTypeToType ze res_ty - ; let (univ_tvs, ex_tvs, eq_preds, res_ty', arg_subst) + ; let (univ_tvs, ex_tvs, eq_preds, arg_subst) = rejigConRes tmpl_bndrs res_tmpl qtkvs res_ty - -- NB: this is a /lazy/ binding, so we pass five thunks to buildDataCon - -- without yet forcing the guards in rejigConRes + -- NB: this is a /lazy/ binding, so we pass four thunks to + -- buildDataCon without yet forcing the guards in rejigConRes -- See Note [Checking GADT return types] -- See Note [Wrong visibility for GADTs] @@ -1611,7 +1611,7 @@ tcConDecl rep_tycon tmpl_bndrs res_tmpl univ_bndrs ex_bndrs eq_preds (substTys arg_subst ctxt) (substTys arg_subst arg_tys) - (substTy arg_subst res_ty') + (substTy arg_subst res_ty) rep_tycon -- NB: we put data_tc, the type constructor gotten from the -- constructor type signature into the data constructor; @@ -1724,7 +1724,7 @@ Both of these bullets are currently violated. GHCi reports MkX's type as MkX :: forall k (a :: k) b. b -> Proxy a -> X a -It turns out that this is a hard to fix. The problem is that GHC expects data +It turns out that this is hard to fix. The problem is that GHC expects data constructors to have their universal variables followed by their existential variables, always. And yet that's violated in the desired type for MkX. Furthermore, given the way that GHC deals with GADT return types ("rejigging", @@ -1782,8 +1782,8 @@ defined yet. So, we want to make rejigConRes lazy and then check the validity of the return type in checkValidDataCon. To do this we /always/ return a -5-tuple from rejigConRes (so that we can extract ret_ty from it, which -checkValidDataCon needs), but the first four fields may be bogus if +4-tuple from rejigConRes (so that we can compute the return type from it, which +checkValidDataCon needs), but the first three fields may be bogus if the return type isn't valid (the last equation for rejigConRes). This is better than an earlier solution which reduced the number of @@ -1808,7 +1808,6 @@ rejigConRes :: [TyConBinder] -> Type -- Template for result type; e.g. -> ([TyVar], -- Universal [TyVar], -- Existential (distinct OccNames from univs) [EqSpec], -- Equality predicates - Type, -- Typechecked return type TCvSubst) -- Substitution to apply to argument types -- We don't check that the TyCon given in the ResTy is -- the same as the parent tycon, because checkValidDataCon will do it @@ -1824,7 +1823,7 @@ rejigConRes tmpl_bndrs res_tmpl dc_tvs res_ty -- b b~z -- z -- Existentials are the leftover type vars: [x,y] - -- So we return ([a,b,z], [x,y], [a~(x,y),b~z], T [(x,y)] z z) + -- So we return ([a,b,z], [x,y], [a~(x,y),b~z], ) | Just subst <- ASSERT( isLiftedTypeKind (typeKind res_ty) ) ASSERT( isLiftedTypeKind (typeKind res_tmpl) ) tcMatchTy res_tmpl res_ty @@ -1835,7 +1834,7 @@ rejigConRes tmpl_bndrs res_tmpl dc_tvs res_ty substed_eqs = map (substEqSpec arg_subst) raw_eqs in - (univ_tvs, substed_ex_tvs, substed_eqs, res_ty, arg_subst) + (univ_tvs, substed_ex_tvs, substed_eqs, arg_subst) | otherwise -- If the return type of the data constructor doesn't match the parent @@ -1848,7 +1847,7 @@ rejigConRes tmpl_bndrs res_tmpl dc_tvs res_ty -- albeit bogus, relying on checkValidDataCon to check the -- bad-result-type error before seeing that the other fields look odd -- See Note [Checking GADT return types] - = (tmpl_tvs, dc_tvs `minusList` tmpl_tvs, [], res_ty, emptyTCvSubst) + = (tmpl_tvs, dc_tvs `minusList` tmpl_tvs, [], emptyTCvSubst) where tmpl_tvs = binderVars tmpl_bndrs From git at git.haskell.org Tue Jul 11 18:36:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 18:36:39 +0000 (UTC) Subject: [commit: ghc] master: Add Template Haskell support for overloaded labels (ec351b8) Message-ID: <20170711183639.BDFB93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ec351b86c1a7f242c5495861ccbd4818c30e521d/ghc >--------------------------------------------------------------- commit ec351b86c1a7f242c5495861ccbd4818c30e521d Author: Matthew Pickering Date: Tue Jul 11 14:01:11 2017 -0400 Add Template Haskell support for overloaded labels Reviewers: RyanGlScott, austin, goldfire, bgamari Reviewed By: RyanGlScott, goldfire, bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3715 >--------------------------------------------------------------- ec351b86c1a7f242c5495861ccbd4818c30e521d libraries/template-haskell/changelog.md | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/libraries/template-haskell/changelog.md b/libraries/template-haskell/changelog.md index 305e39c..8eddedc 100644 --- a/libraries/template-haskell/changelog.md +++ b/libraries/template-haskell/changelog.md @@ -1,5 +1,11 @@ # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell) +## 2.13.0.0 *TBA* + + * Bundled with GHC *TBA* + + * Add support for overloaded labels. Introduces `labelE :: String -> ExpQ`. + ## 2.12.0.0 *TBA* * Bundled with GHC *TBA* From git at git.haskell.org Tue Jul 11 18:36:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 18:36:42 +0000 (UTC) Subject: [commit: ghc] master: Parenthesize infix type names in data declarations in TH printer (ef7fd0a) Message-ID: <20170711183642.7653E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ef7fd0ae8b519b3cd05349753a0e145112c26b67/ghc >--------------------------------------------------------------- commit ef7fd0ae8b519b3cd05349753a0e145112c26b67 Author: Eugene Akentyev Date: Tue Jul 11 13:59:47 2017 -0400 Parenthesize infix type names in data declarations in TH printer Previously datatype names were not paraenthesized (#13887). Reviewers: austin, bgamari, RyanGlScott Reviewed By: RyanGlScott Subscribers: RyanGlScott, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3717 >--------------------------------------------------------------- ef7fd0ae8b519b3cd05349753a0e145112c26b67 libraries/template-haskell/Language/Haskell/TH/Ppr.hs | 7 ++++--- testsuite/tests/th/T10828.stderr | 2 +- testsuite/tests/th/T12403.stdout | 6 +++--- 3 files changed, 8 insertions(+), 7 deletions(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs index 122f0b9..696c445 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs @@ -399,7 +399,7 @@ ppr_data :: Doc -> Cxt -> Name -> Doc -> Maybe Kind -> [Con] -> [DerivClause] ppr_data maybeInst ctxt t argsDoc ksig cs decs = sep [text "data" <+> maybeInst <+> pprCxt ctxt - <+> ppr t <+> argsDoc <+> ksigDoc <+> maybeWhere, + <+> pprName' Applied t <+> argsDoc <+> ksigDoc <+> maybeWhere, nest nestDepth (sep (pref $ map ppr cs)), if null decs then empty @@ -679,8 +679,9 @@ pprStrictType = pprBangType ------------------------------ pprParendType :: Type -> Doc -pprParendType (VarT v) = ppr v -pprParendType (ConT c) = ppr c +pprParendType (VarT v) = pprName' Applied v +-- `Applied` is used here instead of `ppr` because of infix names (#13887) +pprParendType (ConT c) = pprName' Applied c pprParendType (TupleT 0) = text "()" pprParendType (TupleT n) = parens (hcat (replicate (n-1) comma)) pprParendType (UnboxedTupleT n) = hashParens $ hcat $ replicate (n-1) comma diff --git a/testsuite/tests/th/T10828.stderr b/testsuite/tests/th/T10828.stderr index 82509ec..70ed74b 100644 --- a/testsuite/tests/th/T10828.stderr +++ b/testsuite/tests/th/T10828.stderr @@ -8,7 +8,7 @@ newtype Bar_13 :: * -> GHC.Types.Bool -> * = MkBar_14 :: a_15 -> Bar_13 a_15 b_16 data T10828.T (a_0 :: *) where T10828.MkT :: forall (a_1 :: *) . a_1 -> a_1 -> T10828.T a_1 - T10828.MkC :: forall (a_2 :: *) (b_3 :: *) . Data.Type.Equality.~ a_2 + T10828.MkC :: forall (a_2 :: *) (b_3 :: *) . (Data.Type.Equality.~) a_2 GHC.Types.Int => {T10828.foo :: a_2, T10828.bar :: b_3} -> T10828.T GHC.Types.Int data T'_0 a_1 :: * where diff --git a/testsuite/tests/th/T12403.stdout b/testsuite/tests/th/T12403.stdout index 24e222a..386b1c0 100644 --- a/testsuite/tests/th/T12403.stdout +++ b/testsuite/tests/th/T12403.stdout @@ -1,5 +1,5 @@ data Main.T = Main.T ((# , #) GHC.Types.Int - GHC.Types.Int :: GHC.Prim.TYPE (GHC.Types.TupleRep (GHC.Types.: GHC.Types.LiftedRep - (GHC.Types.: GHC.Types.LiftedRep - GHC.Types.[])))) + GHC.Types.Int :: GHC.Prim.TYPE (GHC.Types.TupleRep ((GHC.Types.:) GHC.Types.LiftedRep + ((GHC.Types.:) GHC.Types.LiftedRep + GHC.Types.[])))) From git at git.haskell.org Tue Jul 11 19:26:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 19:26:44 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Fix T13701 allocations yet again (d3bdd6c) Message-ID: <20170711192644.69A813A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d3bdd6c4ea9e267af494f822bfdd0600e3a06281/ghc >--------------------------------------------------------------- commit d3bdd6c4ea9e267af494f822bfdd0600e3a06281 Author: Ben Gamari Date: Tue Jul 11 15:25:53 2017 -0400 testsuite: Fix T13701 allocations yet again >--------------------------------------------------------------- d3bdd6c4ea9e267af494f822bfdd0600e3a06281 testsuite/tests/perf/compiler/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index f8b93aa..4a0d2a2 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -1131,7 +1131,7 @@ test('MultiLayerModules', test('T13701', [ compiler_stats_num_field('bytes allocated', [(platform('x86_64-apple-darwin'), 2217187888, 10), - (platform('x86_64-unknown-linux'), 2467546360, 10), + (platform('x86_64-unknown-linux'), 2187906120, 10), # initial: 2511285600 # 2017-06-23: 2188045288 treat banged variable bindings as FunBinds # 2017-07-11: 2187920960 From git at git.haskell.org Tue Jul 11 19:26:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 19:26:49 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Show stderr output on command failure (20880b5) Message-ID: <20170711192649.D7D0A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/20880b56267059f98ca9ca099b596fb0b7cf0c7e/ghc >--------------------------------------------------------------- commit 20880b56267059f98ca9ca099b596fb0b7cf0c7e Author: Ben Gamari Date: Tue Jul 11 14:43:38 2017 -0400 testsuite: Show stderr output on command failure Reviewers: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3716 >--------------------------------------------------------------- 20880b56267059f98ca9ca099b596fb0b7cf0c7e testsuite/driver/testutil.py | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/driver/testutil.py b/testsuite/driver/testutil.py index d35fb81..dcba177 100644 --- a/testsuite/driver/testutil.py +++ b/testsuite/driver/testutil.py @@ -22,7 +22,7 @@ def getStdout(cmd_and_args): if r != 0: raise Exception("Command failed: " + str(cmd_and_args)) if stderr: - raise Exception("stderr from command: " + str(cmd_and_args)) + raise Exception("stderr from command: %s\nOutput:\n%s\n" % (cmd_and_args, stderr)) return stdout def mkdirp(path): From git at git.haskell.org Tue Jul 11 19:26:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 19:26:47 +0000 (UTC) Subject: [commit: ghc] master: StgLint: Don't loop on tycons with runtime rep arguments (be04c16) Message-ID: <20170711192647.28AA23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/be04c16b0e5fe9d50562e0868b890b0f9b778a41/ghc >--------------------------------------------------------------- commit be04c16b0e5fe9d50562e0868b890b0f9b778a41 Author: Ben Gamari Date: Tue Jul 11 14:43:19 2017 -0400 StgLint: Don't loop on tycons with runtime rep arguments Test Plan: Validate Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #13941 Differential Revision: https://phabricator.haskell.org/D3714 >--------------------------------------------------------------- be04c16b0e5fe9d50562e0868b890b0f9b778a41 compiler/stgSyn/StgLint.hs | 25 +++++++++++++++++++------ 1 file changed, 19 insertions(+), 6 deletions(-) diff --git a/compiler/stgSyn/StgLint.hs b/compiler/stgSyn/StgLint.hs index 7a1ed4d..cbfd11b 100644 --- a/compiler/stgSyn/StgLint.hs +++ b/compiler/stgSyn/StgLint.hs @@ -27,7 +27,6 @@ import Util import SrcLoc import Outputable import Control.Monad -import Data.Function #include "HsVersions.h" @@ -419,18 +418,32 @@ stgEqType :: Type -> Type -> Bool -- Fundamentally this is a losing battle because of unsafeCoerce stgEqType orig_ty1 orig_ty2 - = gos (typePrimRep orig_ty1) (typePrimRep orig_ty2) + = gos orig_ty1 orig_ty2 where - gos :: [PrimRep] -> [PrimRep] -> Bool - gos [_] [_] = go orig_ty1 orig_ty2 - gos reps1 reps2 = reps1 == reps2 + gos :: Type -> Type -> Bool + gos ty1 ty2 + -- These have no prim rep + | isRuntimeRepKindedTy ty1 && isRuntimeRepKindedTy ty2 + = True + + -- We have a unary type + | [_] <- reps1, [_] <- reps2 + = go ty1 ty2 + + -- In the case of a tuple just compare prim reps + | otherwise + = reps1 == reps2 + where + reps1 = typePrimRep ty1 + reps2 = typePrimRep ty2 go :: UnaryType -> UnaryType -> Bool go ty1 ty2 | Just (tc1, tc_args1) <- splitTyConApp_maybe ty1 , Just (tc2, tc_args2) <- splitTyConApp_maybe ty2 , let res = if tc1 == tc2 - then equalLength tc_args1 tc_args2 && and (zipWith (gos `on` typePrimRep) tc_args1 tc_args2) + then equalLength tc_args1 tc_args2 + && and (zipWith gos tc_args1 tc_args2) else -- TyCons don't match; but don't bleat if either is a -- family TyCon because a coercion might have made it -- equal to something else From git at git.haskell.org Tue Jul 11 19:26:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 19:26:52 +0000 (UTC) Subject: [commit: ghc] master: configure: Ensure that we don't set LD to unusable linker (fcd2db1) Message-ID: <20170711192652.97DD73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fcd2db14368fc6e0d35b13535a9663cfab7080a7/ghc >--------------------------------------------------------------- commit fcd2db14368fc6e0d35b13535a9663cfab7080a7 Author: Ben Gamari Date: Tue Jul 11 14:42:04 2017 -0400 configure: Ensure that we don't set LD to unusable linker Previously if we found an unusable linker in PATH (e.g. ld.lld on OS X) we would notice the -fuse-ld=... was broken, but neglected to reset LD to a usable linker. This resulted in brokenness on OS X when lld is in PATH. Test Plan: Validate on OS X with lld in PATH Reviewers: austin, hvr, angerman Reviewed By: angerman Subscribers: rwbarton, thomie, erikd, angerman GHC Trac Issues: #13541 Differential Revision: https://phabricator.haskell.org/D3713 >--------------------------------------------------------------- fcd2db14368fc6e0d35b13535a9663cfab7080a7 aclocal.m4 | 12 +++++++----- 1 file changed, 7 insertions(+), 5 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 1d9c09b..c31c881 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2272,18 +2272,20 @@ AC_DEFUN([FIND_LD],[ [enable_ld_override=yes]) if test "x$enable_ld_override" = "xyes"; then - AC_CHECK_TARGET_TOOLS([LD], [ld.gold ld.lld ld]) - UseLd='' + AC_CHECK_TARGET_TOOLS([TmpLd], [ld.gold ld.lld ld]) - out=`$LD --version` + out=`$TmpLd --version` case $out in "GNU ld"*) FP_CC_LINKER_FLAG_TRY(bfd, $2) ;; "GNU gold"*) FP_CC_LINKER_FLAG_TRY(gold, $2) ;; "LLD"*) FP_CC_LINKER_FLAG_TRY(lld, $2) ;; *) AC_MSG_NOTICE([unknown linker version $out]) ;; esac - if test "z$2" = "z"; then - AC_MSG_NOTICE([unable to convince '$CC' to use linker '$LD']) + if test "z$$2" = "z"; then + AC_MSG_NOTICE([unable to convince '$CC' to use linker '$TmpLd']) + AC_CHECK_TARGET_TOOL([LD], [ld]) + else + LD="$TmpLd" fi else AC_CHECK_TARGET_TOOL([LD], [ld]) From git at git.haskell.org Tue Jul 11 20:33:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 20:33:20 +0000 (UTC) Subject: [commit: ghc] master: Fix minor typo (a0d9169) Message-ID: <20170711203320.396613A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a0d9169362b4cc47f8eb323f96dd18e6e9c6728a/ghc >--------------------------------------------------------------- commit a0d9169362b4cc47f8eb323f96dd18e6e9c6728a Author: Ismail Date: Fri Jul 7 17:19:33 2017 +0100 Fix minor typo >--------------------------------------------------------------- a0d9169362b4cc47f8eb323f96dd18e6e9c6728a libraries/base/Control/Exception.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/Control/Exception.hs b/libraries/base/Control/Exception.hs index 88938e2..93ba3d5 100644 --- a/libraries/base/Control/Exception.hs +++ b/libraries/base/Control/Exception.hs @@ -376,7 +376,7 @@ handled differently. Instead, you would probably want something like: > e <- tryJust (guard . isDoesNotExistError) (readFile f) > let str = either (const "") id e -There are occassions when you really do need to catch any sort of +There are occasions when you really do need to catch any sort of exception. However, in most cases this is just so you can do some cleaning up; you aren't actually interested in the exception itself. For example, if you open a file then you want to close it again, From git at git.haskell.org Tue Jul 11 20:41:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 20:41:46 +0000 (UTC) Subject: [commit: ghc] master: Remove redundant import; fix note (3a163aa) Message-ID: <20170711204146.5FB253A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3a163aabe7948d382393e9e81f1239f3e06b222b/ghc >--------------------------------------------------------------- commit 3a163aabe7948d382393e9e81f1239f3e06b222b Author: David Feuer Date: Tue Jul 11 15:28:49 2017 -0400 Remove redundant import; fix note * Remove the redundant import of `Data.Maybe` from `GHC.Foreign`. * Fix the note in `GHC.Stack.Types` to give a correct explanation of the problematic cycle. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3722 >--------------------------------------------------------------- 3a163aabe7948d382393e9e81f1239f3e06b222b libraries/base/GHC/Foreign.hs | 1 - libraries/base/GHC/Stack/Types.hs | 8 +++----- 2 files changed, 3 insertions(+), 6 deletions(-) diff --git a/libraries/base/GHC/Foreign.hs b/libraries/base/GHC/Foreign.hs index 6d2f8c1..eb5e853 100644 --- a/libraries/base/GHC/Foreign.hs +++ b/libraries/base/GHC/Foreign.hs @@ -49,7 +49,6 @@ import Data.Word -- Imports for the locale-encoding version of marshallers import Data.Tuple (fst) -import Data.Maybe import GHC.Show ( show ) diff --git a/libraries/base/GHC/Stack/Types.hs b/libraries/base/GHC/Stack/Types.hs index 29be6d6..54352b1 100644 --- a/libraries/base/GHC/Stack/Types.hs +++ b/libraries/base/GHC/Stack/Types.hs @@ -41,12 +41,10 @@ Ideally these would live in GHC.Stack but sadly they can't due to this import cycle, Module imports form a cycle: - module ‘Data.Maybe’ (libraries/base/Data/Maybe.hs) - imports ‘GHC.Base’ (libraries/base/GHC/Base.hs) - which imports ‘GHC.Err’ (libraries/base/GHC/Err.hs) + module ‘GHC.Base’ (libraries/base/GHC/Base.hs) + imports ‘GHC.Err’ (libraries/base/GHC/Err.hs) which imports ‘GHC.Stack’ (libraries/base/dist-install/build/GHC/Stack.hs) - which imports ‘GHC.Foreign’ (libraries/base/GHC/Foreign.hs) - which imports ‘Data.Maybe’ (libraries/base/Data/Maybe.hs) + which imports ‘GHC.Base‘ (libraries/base/GHC/Base.hs) -} import GHC.Classes (Eq) From git at git.haskell.org Tue Jul 11 20:41:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 20:41:43 +0000 (UTC) Subject: [commit: ghc] master: Use correct section types syntax for architecture (9b9f978) Message-ID: <20170711204143.A87753A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9b9f978fdcd13ff7b2a9b7391e02dff06da622a0/ghc >--------------------------------------------------------------- commit 9b9f978fdcd13ff7b2a9b7391e02dff06da622a0 Author: Ben Gamari Date: Tue Jul 11 15:41:55 2017 -0400 Use correct section types syntax for architecture Previously GHC would always assume that section types began with `@` while producing assembly, which is not true. For instance, in ARM assembly syntax section types begin with `%`. This abstracts out section type pretty-printing and adjusts it to correctly account for the target architectures assembly flavor. Reviewers: austin, hvr, Phyx Reviewed By: Phyx Subscribers: Phyx, rwbarton, thomie, erikd GHC Trac Issues: #13937 Differential Revision: https://phabricator.haskell.org/D3712 >--------------------------------------------------------------- 9b9f978fdcd13ff7b2a9b7391e02dff06da622a0 aclocal.m4 | 11 ++++++++++- compiler/ghc.cabal.in | 1 + compiler/main/DriverPipeline.hs | 6 ++++-- compiler/main/Elf.hs | 14 ++++---------- compiler/nativeGen/AsmCodeGen.hs | 3 ++- compiler/nativeGen/Dwarf/Constants.hs | 10 ++++++---- compiler/nativeGen/PprBase.hs | 3 ++- compiler/utils/AsmUtils.hs | 18 ++++++++++++++++++ 8 files changed, 47 insertions(+), 19 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index c31c881..71a874f 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -321,9 +321,18 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS], dnl so we empty CFLAGS while running this test CFLAGS2="$CFLAGS" CFLAGS= + case $TargetArch in + arm) + dnl See #13937. + progbits="%progbits" + ;; + *) + progbits="@progbits" + ;; + esac AC_MSG_CHECKING(for GNU non-executable stack support) AC_COMPILE_IFELSE( - [AC_LANG_PROGRAM([__asm__ (".section .note.GNU-stack,\"\", at progbits");], [0])], + [AC_LANG_PROGRAM([__asm__ (".section .note.GNU-stack,\"\",$progbits");], [0])], [AC_MSG_RESULT(yes) HaskellHaveGnuNonexecStack=True], [AC_MSG_RESULT(no) diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index 1427a51..f40c8ba 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -170,6 +170,7 @@ Library NameShape RnModIface Avail + AsmUtils BasicTypes ConLike DataCon diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index ad0e0c8..a6873fb 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -35,6 +35,7 @@ module DriverPipeline ( #include "HsVersions.h" +import AsmUtils import PipelineMonad import Packages import HeaderInfo @@ -1714,14 +1715,15 @@ mkNoteObjsToLinkIntoBinary dflags dep_packages = do where link_opts info = hcat [ -- "link info" section (see Note [LinkInfo section]) - makeElfNote dflags ghcLinkInfoSectionName ghcLinkInfoNoteName 0 info, + makeElfNote ghcLinkInfoSectionName ghcLinkInfoNoteName 0 info, -- ALL generated assembly must have this section to disable -- executable stacks. See also -- compiler/nativeGen/AsmCodeGen.hs for another instance -- where we need to do this. if platformHasGnuNonexecStack (targetPlatform dflags) - then text ".section .note.GNU-stack,\"\", at progbits\n" + then text ".section .note.GNU-stack,\"\"," + <> sectionType "progbits" <> char '\n' else Outputable.empty ] diff --git a/compiler/main/Elf.hs b/compiler/main/Elf.hs index 50f11a7..599d4d9 100644 --- a/compiler/main/Elf.hs +++ b/compiler/main/Elf.hs @@ -14,9 +14,9 @@ module Elf ( makeElfNote ) where +import AsmUtils import Exception import DynFlags -import Platform import ErrUtils import Maybes (MaybeT(..),runMaybeT) import Util (charToC) @@ -415,12 +415,12 @@ readElfNoteAsString dflags path sectionName noteId = action `catchIO` \_ -> do -- If we add new target platforms, we need to check that the generated words -- are 32-bit long, otherwise we need to use platform specific directives to -- force 32-bit .int in asWord32. -makeElfNote :: DynFlags -> String -> String -> Word32 -> String -> SDoc -makeElfNote dflags sectionName noteName typ contents = hcat [ +makeElfNote :: String -> String -> Word32 -> String -> SDoc +makeElfNote sectionName noteName typ contents = hcat [ text "\t.section ", text sectionName, text ",\"\",", - text elfSectionNote, + sectionType "note", text "\n", -- note name length (+ 1 for ending \0) @@ -453,12 +453,6 @@ makeElfNote dflags sectionName noteName typ contents = hcat [ text (show x), text "\n"] - elfSectionNote :: String - elfSectionNote = case platformArch (targetPlatform dflags) of - ArchARM _ _ _ -> "%note" - _ -> "@note" - - ------------------ -- Helpers diff --git a/compiler/nativeGen/AsmCodeGen.hs b/compiler/nativeGen/AsmCodeGen.hs index e7a3efd..45d170e 100644 --- a/compiler/nativeGen/AsmCodeGen.hs +++ b/compiler/nativeGen/AsmCodeGen.hs @@ -51,6 +51,7 @@ import qualified RegAlloc.Graph.Main as Color import qualified RegAlloc.Graph.Stats as Color import qualified RegAlloc.Graph.TrivColorable as Color +import AsmUtils import TargetReg import Platform import Config @@ -770,7 +771,7 @@ makeImportsDoc dflags imports -- security. GHC generated code does not need an executable -- stack so add the note in: (if platformHasGnuNonexecStack platform - then text ".section .note.GNU-stack,\"\", at progbits" + then text ".section .note.GNU-stack,\"\"," <> sectionType "progbits" else Outputable.empty) $$ -- And just because every other compiler does, let's stick in diff --git a/compiler/nativeGen/Dwarf/Constants.hs b/compiler/nativeGen/Dwarf/Constants.hs index 880c7d7..a8034ef 100644 --- a/compiler/nativeGen/Dwarf/Constants.hs +++ b/compiler/nativeGen/Dwarf/Constants.hs @@ -3,6 +3,7 @@ module Dwarf.Constants where +import AsmUtils import FastString import Platform import Outputable @@ -150,14 +151,15 @@ dwarfGhcSection = dwarfSection "ghc" dwarfARangesSection = dwarfSection "aranges" dwarfSection :: String -> SDoc -dwarfSection name = sdocWithPlatform $ \plat -> ftext $ mkFastString $ +dwarfSection name = sdocWithPlatform $ \plat -> case platformOS plat of os | osElfTarget os - -> "\t.section .debug_" ++ name ++ ",\"\", at progbits" + -> text "\t.section .debug_" <> text name <> text ",\"\"," + <> sectionType "progbits" | osMachOTarget os - -> "\t.section __DWARF,__debug_" ++ name ++ ",regular,debug" + -> text "\t.section __DWARF,__debug_" <> text name <> text ",regular,debug" | otherwise - -> "\t.section .debug_" ++ name ++ ",\"dr\"" + -> text "\t.section .debug_" <> text name <> text ",\"dr\"" -- * Dwarf section labels dwarfInfoLabel, dwarfAbbrevLabel, dwarfLineLabel, dwarfFrameLabel :: LitString diff --git a/compiler/nativeGen/PprBase.hs b/compiler/nativeGen/PprBase.hs index 76ac13e..aca4274 100644 --- a/compiler/nativeGen/PprBase.hs +++ b/compiler/nativeGen/PprBase.hs @@ -16,6 +16,7 @@ module PprBase ( where +import AsmUtils import CLabel import Cmm import DynFlags @@ -131,7 +132,7 @@ pprGNUSectionHeader sep t suffix = sdocWithDynFlags $ \dflags -> CString | OSMinGW32 <- platformOS (targetPlatform dflags) -> empty - | otherwise -> text ",\"aMS\", at progbits,1" + | otherwise -> text ",\"aMS\"," <> sectionType "progbits" <> text ",1" _ -> empty -- XCOFF doesn't support relocating label-differences, so we place all diff --git a/compiler/utils/AsmUtils.hs b/compiler/utils/AsmUtils.hs new file mode 100644 index 0000000..55f9d6d --- /dev/null +++ b/compiler/utils/AsmUtils.hs @@ -0,0 +1,18 @@ +-- | Various utilities used in generating assembler. +-- +-- These are used not only by the native code generator, but also by the +-- "DriverPipeline". +module AsmUtils + ( sectionType + ) where + +import Platform +import Outputable + +-- | Generate a section type (e.g. @\@progbits@). See #13937. +sectionType :: String -- ^ section type + -> SDoc -- ^ pretty assembler fragment +sectionType ty = sdocWithPlatform $ \platform -> + case platformArch platform of + ArchARM{} -> char '%' <> text ty + _ -> char '@' <> text ty From git at git.haskell.org Tue Jul 11 20:41:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Jul 2017 20:41:50 +0000 (UTC) Subject: [commit: ghc] master: Mention which -Werror promoted a warning to an error (4befb41) Message-ID: <20170711204150.29CDA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4befb415d7ee63d2b0ecdc2384310dc4b3ccc90a/ghc >--------------------------------------------------------------- commit 4befb415d7ee63d2b0ecdc2384310dc4b3ccc90a Author: Ömer Sinan Ağacan Date: Tue Jul 11 15:41:20 2017 -0400 Mention which -Werror promoted a warning to an error Previously -Werror or -Werror=flag printed warnings as usual and then printed these two lines: : error: Failing due to -Werror. This is not ideal: first, it's not clear which flag made one of the warnings an error. Second, warning messages are not modified in any way, so there's no way to know which warnings caused this error. With this patch we (1) promote warning messages to error messages if a relevant -Werror is enabled (2) mention which -Werror is used during this promotion. Previously: [1 of 1] Compiling Main ( test.hs, test.o ) test.hs:9:10: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In a case alternative: Patterns not matched: (C2 _) | 9 | sInt s = case s of | ^^^^^^^^^... test.hs:12:14: warning: [-Wmissing-fields] • Fields of ‘Rec’ not initialised: f2 • In the first argument of ‘print’, namely ‘Rec {f1 = 1}’ In the expression: print Rec {f1 = 1} In an equation for ‘main’: main = print Rec {f1 = 1} | 12 | main = print Rec{ f1 = 1 } | ^^^^^^^^^^^^^ : error: Failing due to -Werror. Now: [1 of 1] Compiling Main ( test.hs, test.o ) test.hs:9:10: error: [-Wincomplete-patterns, -Werror=incomplete-patterns] Pattern match(es) are non-exhaustive In a case alternative: Patterns not matched: (C2 _) | 9 | sInt s = case s of | ^^^^^^^^^... test.hs:12:14: error: [-Wmissing-fields, -Werror=missing-fields] • Fields of ‘Rec’ not initialised: f2 • In the first argument of ‘print’, namely ‘Rec {f1 = 1}’ In the expression: print Rec {f1 = 1} In an equation for ‘main’: main = print Rec {f1 = 1} | 12 | main = print Rec{ f1 = 1 } | ^^^^^^^^^^^^^ Test Plan: - Update old tests, add new tests if there aren't any relevant tests Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3709 >--------------------------------------------------------------- 4befb415d7ee63d2b0ecdc2384310dc4b3ccc90a compiler/main/DynFlags.hs | 79 ++++++++++++++-------- compiler/main/ErrUtils.hs | 19 +++--- compiler/main/HscTypes.hs | 24 +++++-- compiler/rename/RnNames.hs | 3 +- compiler/typecheck/Inst.hs | 6 +- compiler/typecheck/TcRnExports.hs | 16 ++--- compiler/typecheck/TcRnMonad.hs | 19 +++--- compiler/typecheck/TcSigs.hs | 2 +- testsuite/tests/driver/T11429c.stderr | 6 +- testsuite/tests/driver/werror.stderr | 19 +++--- .../should_fail/overloadedrecfldsfail05.stderr | 5 +- .../should_fail/overloadedrecfldsfail06.stderr | 11 ++- .../should_fail/overloadedrecfldsfail11.stderr | 5 +- .../should_fail/overloadedrecfldsfail12.stderr | 9 +-- .../tests/patsyn/should_fail/UnliftedPSBind.stderr | 5 +- .../tests/patsyn/should_fail/unboxed-bind.stderr | 5 +- testsuite/tests/rename/should_fail/T5892a.stderr | 5 +- .../tests/safeHaskell/flags/SafeFlags18.stderr | 7 +- .../tests/safeHaskell/flags/SafeFlags23.stderr | 5 +- .../tests/safeHaskell/flags/SafeFlags26.stderr | 5 +- .../safeHaskell/overlapping/SH_Overlap7.stderr | 5 +- .../safeHaskell/safeInfered/UnsafeInfered12.stderr | 5 +- testsuite/tests/typecheck/should_fail/T3966.stderr | 5 +- .../tests/typecheck/should_fail/tcfail204.stderr | 5 +- .../tests/warnings/should_fail/WerrorFail.stderr | 6 +- .../tests/warnings/should_fail/WerrorFail2.hs | 19 ++++++ .../tests/warnings/should_fail/WerrorFail2.stderr | 16 +++++ testsuite/tests/warnings/should_fail/all.T | 1 + 28 files changed, 169 insertions(+), 148 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 4befb415d7ee63d2b0ecdc2384310dc4b3ccc90a From git at git.haskell.org Wed Jul 12 05:08:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Jul 2017 05:08:23 +0000 (UTC) Subject: [commit: ghc] master: Fix missing escape in macro (1ee49cb) Message-ID: <20170712050823.B40763A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1ee49cb11c7ad1af20c117a5395df96ded9a729f/ghc >--------------------------------------------------------------- commit 1ee49cb11c7ad1af20c117a5395df96ded9a729f Author: Moritz Angermann Date: Wed Jul 12 01:09:11 2017 -0400 Fix missing escape in macro Reviewers: angerman, austin, bgamari, erikd, simonmar Reviewed By: angerman Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3727 >--------------------------------------------------------------- 1ee49cb11c7ad1af20c117a5395df96ded9a729f rts/Trace.h | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/Trace.h b/rts/Trace.h index 624d459..a72248a 100644 --- a/rts/Trace.h +++ b/rts/Trace.h @@ -398,7 +398,7 @@ void dtraceUserMarkerWrapper(Capability *cap, char *msg); par_n_threads, \ par_max_copied, \ par_tot_copied, \ - par_balanced_copied) + par_balanced_copied) \ HASKELLEVENT_GC_STATS(heap_capset, gens, \ copies, slop, fragmentation, \ par_n_threads, \ From git at git.haskell.org Wed Jul 12 12:55:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Jul 2017 12:55:15 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Update haddock allocations (5743581) Message-ID: <20170712125515.99C723A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/57435810c1ee41c5a4222cd8957380cb5477cb5b/ghc >--------------------------------------------------------------- commit 57435810c1ee41c5a4222cd8957380cb5477cb5b Author: Ben Gamari Date: Wed Jul 12 08:21:55 2017 -0400 testsuite: Update haddock allocations It seems to be the change to getNameToInstancesIndex that bumped these. >--------------------------------------------------------------- 57435810c1ee41c5a4222cd8957380cb5477cb5b testsuite/tests/perf/haddock/all.T | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index 64a6449..7aed869 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -9,7 +9,7 @@ test('haddock.base', [(platform('x86_64-unknown-mingw32'), 24286343184, 5) # 2017-02-19 24286343184 (x64/Windows) - Generalize kind of (->) - ,(wordsize(64), 25173968808, 5) + ,(wordsize(64), 23677299848, 5) # 2012-08-14: 5920822352 (amd64/Linux) # 2012-09-20: 5829972376 (amd64/Linux) # 2012-10-08: 5902601224 (amd64/Linux) @@ -41,6 +41,7 @@ test('haddock.base', # 2017-02-12: 25592972912 (x86_64/Linux) - Type-indexed Typeable # 2017-06-05: 27868466432 (x86_64/Linux) - Desugar modules compiled with -fno-code # 2017-06-06: 25173968808 (x86_64/Linux) - Don't pass on -dcore-lint in Haddock.mk + # 2017-07-12: 23677299848 (x86_64/Linux) - Use getNameToInstancesIndex ,(platform('i386-unknown-mingw32'), 2885173512, 5) # 2013-02-10: 3358693084 (x86/Windows) @@ -138,7 +139,7 @@ test('haddock.compiler', [extra_files(['../../../../compiler/stage2/haddock.t']), unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 55990521024 , 10) + [(wordsize(64), 51592019560, 10) # 2012-08-14: 26070600504 (amd64/Linux) # 2012-08-29: 26353100288 (amd64/Linux, new CG) # 2012-09-18: 26882813032 (amd64/Linux) @@ -159,6 +160,7 @@ test('haddock.compiler', # 2017-05-31: 52762752968 (amd64/Linux) Faster checkFamInstConsistency # 2017-06-05: 65378619232 (amd64/Linux) Desugar modules compiled with -fno-code # 2017-06-06: 55990521024 (amd64/Linux) Don't pass on -dcore-lint in Haddock.mk + # 2017-07-12: 51592019560 (amd64/Linux) Use getNameToInstancesIndex ,(platform('i386-unknown-mingw32'), 367546388, 10) # 2012-10-30: 13773051312 (x86/Windows) From git at git.haskell.org Wed Jul 12 12:55:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Jul 2017 12:55:18 +0000 (UTC) Subject: [commit: ghc] master: distrib/configure: Fail if we can't detect machine's word size (60ec8f7) Message-ID: <20170712125518.53BB03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/60ec8f74d32a9976ac8ddf6fd366218283fcac3e/ghc >--------------------------------------------------------------- commit 60ec8f74d32a9976ac8ddf6fd366218283fcac3e Author: Ben Gamari Date: Tue Jul 11 18:40:31 2017 -0400 distrib/configure: Fail if we can't detect machine's word size This is a sure sign that something is terribly wrong. We also now verify that the word size that the binary distribution expects matches the word size produced by the local target toolchain. Finally we rename WordSize to TargetWordSize, since non-host/target qualified quantities are terribly confusing. Reviewers: austin, hvr, Phyx Reviewed By: Phyx Subscribers: Phyx, rwbarton, thomie, erikd Differential Revision: https://phabricator.haskell.org/D3711 >--------------------------------------------------------------- 60ec8f74d32a9976ac8ddf6fd366218283fcac3e configure.ac | 4 ++-- distrib/configure.ac.in | 16 +++++++++++++--- settings.in | 2 +- 3 files changed, 16 insertions(+), 6 deletions(-) diff --git a/configure.ac b/configure.ac index c31deba..043dea8 100644 --- a/configure.ac +++ b/configure.ac @@ -875,8 +875,8 @@ FP_CHECK_SIZEOF_AND_ALIGNMENT(uint64_t) dnl for use in settings.in -WordSize=$ac_cv_sizeof_void_p -AC_SUBST(WordSize) +TargetWordSize=$ac_cv_sizeof_void_p +AC_SUBST(TargetWordSize) FP_CHECK_FUNC([WinExec], [@%:@include ], [WinExec("",0)]) diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index ac6af24..a15b4a5 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -134,10 +134,20 @@ dnl May need to use gcc to find platform details. dnl -------------------------------------------------------------- FPTOOLS_SET_HASKELL_PLATFORM_VARS -dnl WordSize for settings.in +dnl TargetWordSize for settings.in AC_CHECK_SIZEOF(void *, 4) -WordSize=$ac_cv_sizeof_void_p -AC_SUBST(WordSize) +if test "x$ac_cv_sizeof_void_p" = "x0"; then + AC_MSG_ERROR([Failed to determine machine word size. Does your toolchain actually work?]) +fi +dnl Check that the toolchain we have is consistent with what the compiler expects +if test "x$ac_cv_sizeof_void_p" != "x at TargetWordSize@"; then + AC_MSG_ERROR([This binary distribution produces binaries for a target with + word size of @TargetWordSize@, but your target toolchain produces binaries + with a word size of $ac_cv_sizeof_void_p. Are you sure your toolchain + targets the intended target platform of this compiler?]) +fi +TargetWordSize=$ac_cv_sizeof_void_p +AC_SUBST(TargetWordSize) # dnl ** how to invoke `ar' and `ranlib' diff --git a/settings.in b/settings.in index 04b913b..df647f1 100644 --- a/settings.in +++ b/settings.in @@ -22,7 +22,7 @@ ("cross compiling", "@CrossCompiling@"), ("target os", "@HaskellTargetOs@"), ("target arch", "@HaskellTargetArch@"), - ("target word size", "@WordSize@"), + ("target word size", "@TargetWordSize@"), ("target has GNU nonexec stack", "@HaskellHaveGnuNonexecStack@"), ("target has .ident directive", "@HaskellHaveIdentDirective@"), ("target has subsections via symbols", "@HaskellHaveSubsectionsViaSymbols@"), From git at git.haskell.org Wed Jul 12 12:55:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Jul 2017 12:55:21 +0000 (UTC) Subject: [commit: ghc] master: [iserv] Fixing the word size for RemotePtr and toWordArray (7ae4a28) Message-ID: <20170712125521.CC4B33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7ae4a28f6a09a0540aab59f5a03fdbcd46a99f17/ghc >--------------------------------------------------------------- commit 7ae4a28f6a09a0540aab59f5a03fdbcd46a99f17 Author: Ben Gamari Date: Tue Jul 11 20:50:38 2017 -0400 [iserv] Fixing the word size for RemotePtr and toWordArray 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. When dealing with a host and target of different word size (say host hast 64bit, target has 32bit), we need to fix the RemotePtr size and the toWordArray function, as they are part of the iserv ResolvedBCO binary protocol. This needs to be word size independent. The choice for RemotePtr to 64bit was made to ensure we can store 64bit pointers when targeting 64bit. The choice for 32bit word arrays was made wrt. encoding/decoding on the potentially slower device. The efficient serialization code has been graciously provided by @bgamari. Reviewers: bgamari, simonmar, austin, hvr Reviewed By: bgamari Subscribers: Ericson2314, rwbarton, thomie, ryantrinkle Differential Revision: https://phabricator.haskell.org/D3443 >--------------------------------------------------------------- 7ae4a28f6a09a0540aab59f5a03fdbcd46a99f17 compiler/ghci/ByteCodeAsm.hs | 2 +- compiler/ghci/ByteCodeLink.hs | 18 ++---- compiler/ghci/ByteCodeTypes.hs | 2 +- libraries/ghci/GHCi/BinaryArray.hs | 77 ++++++++++++++++++++++++++ libraries/ghci/GHCi/CreateBCO.hs | 15 ++++- libraries/ghci/GHCi/RemoteTypes.hs | 12 ++-- libraries/ghci/GHCi/ResolvedBCO.hs | 68 +++++++++-------------- libraries/ghci/ghci.cabal.in | 1 + testsuite/tests/ghci/should_run/BinaryArray.hs | 29 ++++++++++ testsuite/tests/ghci/should_run/all.T | 1 + 10 files changed, 158 insertions(+), 67 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 7ae4a28f6a09a0540aab59f5a03fdbcd46a99f17 From git at git.haskell.org Wed Jul 12 19:11:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Jul 2017 19:11:58 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Again update allocations of T13701 (4700baa) Message-ID: <20170712191158.F3B3F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4700baaf8f9bf3c44a53a595d840c7c14cfd6f98/ghc >--------------------------------------------------------------- commit 4700baaf8f9bf3c44a53a595d840c7c14cfd6f98 Author: Ben Gamari Date: Wed Jul 12 15:10:46 2017 -0400 testsuite: Again update allocations of T13701 This test appears to be quite unstable. >--------------------------------------------------------------- 4700baaf8f9bf3c44a53a595d840c7c14cfd6f98 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 4a0d2a2..a2728ca 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -1131,10 +1131,11 @@ test('MultiLayerModules', test('T13701', [ compiler_stats_num_field('bytes allocated', [(platform('x86_64-apple-darwin'), 2217187888, 10), - (platform('x86_64-unknown-linux'), 2187906120, 10), + (platform('x86_64-unknown-linux'), 2412223768, 10), # initial: 2511285600 # 2017-06-23: 2188045288 treat banged variable bindings as FunBinds # 2017-07-11: 2187920960 + # 2017-07-12: 2412223768 inconsistency between Ben's machine and Harbormaster? ]), pre_cmd('./genT13701'), extra_files(['genT13701']), From git at git.haskell.org Wed Jul 12 23:28:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Jul 2017 23:28:22 +0000 (UTC) Subject: [commit: ghc] master: Fix some excessive spacing in error messages (1909985) Message-ID: <20170712232822.8C10D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1909985b412866d9fa1dde51d36b1cf7ff6de8a6/ghc >--------------------------------------------------------------- commit 1909985b412866d9fa1dde51d36b1cf7ff6de8a6 Author: Ryan Scott Date: Wed Jul 12 19:26:37 2017 -0400 Fix some excessive spacing in error messages Test Plan: If it builds, ship it Reviewers: austin, bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3729 >--------------------------------------------------------------- 1909985b412866d9fa1dde51d36b1cf7ff6de8a6 compiler/typecheck/TcClassDcl.hs | 2 +- testsuite/tests/deriving/should_fail/drvfail011.stderr | 18 +++++++++--------- .../tests/indexed-types/should_compile/Simple2.stderr | 8 ++++---- testsuite/tests/typecheck/should_compile/tc254.stderr | 2 +- 4 files changed, 15 insertions(+), 15 deletions(-) diff --git a/compiler/typecheck/TcClassDcl.hs b/compiler/typecheck/TcClassDcl.hs index 4701197..a3e9549 100644 --- a/compiler/typecheck/TcClassDcl.hs +++ b/compiler/typecheck/TcClassDcl.hs @@ -521,5 +521,5 @@ warnMissingAT name -- Warn only if -Wmissing-methods AND not a signature ; warnTc (Reason Opt_WarnMissingMethods) (warn && hsc_src /= HsigFile) (text "No explicit" <+> text "associated type" - <+> text "or default declaration for " + <+> text "or default declaration for" <+> quotes (ppr name)) } diff --git a/testsuite/tests/deriving/should_fail/drvfail011.stderr b/testsuite/tests/deriving/should_fail/drvfail011.stderr index 6ea42e1..e29f4e7 100644 --- a/testsuite/tests/deriving/should_fail/drvfail011.stderr +++ b/testsuite/tests/deriving/should_fail/drvfail011.stderr @@ -1,10 +1,10 @@ -drvfail011.hs:8:1: - No instance for (Eq a) arising from a use of ‘==’ - Possible fix: add (Eq a) to the context of the instance declaration - In the expression: ((a1 == b1)) - In an equation for ‘==’: (==) (T1 a1) (T1 b1) = ((a1 == b1)) - When typechecking the code for ‘==’ - in a derived instance for ‘Eq (T a)’: - To see the code I am typechecking, use -ddump-deriv - In the instance declaration for ‘Eq (T a)’ +drvfail011.hs:8:1: error: + • No instance for (Eq a) arising from a use of ‘==’ + Possible fix: add (Eq a) to the context of the instance declaration + • In the expression: ((a1 == b1)) + In an equation for ‘==’: (==) (T1 a1) (T1 b1) = ((a1 == b1)) + When typechecking the code for ‘==’ + in a derived instance for ‘Eq (T a)’: + To see the code I am typechecking, use -ddump-deriv + In the instance declaration for ‘Eq (T a)’ diff --git a/testsuite/tests/indexed-types/should_compile/Simple2.stderr b/testsuite/tests/indexed-types/should_compile/Simple2.stderr index 4b3b0f6..c43280e 100644 --- a/testsuite/tests/indexed-types/should_compile/Simple2.stderr +++ b/testsuite/tests/indexed-types/should_compile/Simple2.stderr @@ -1,6 +1,6 @@ Simple2.hs:21:1: warning: [-Wmissing-methods (in -Wdefault)] - • No explicit associated type or default declaration for ‘S3n’ + • No explicit associated type or default declaration for ‘S3n’ • In the instance declaration for ‘C3 Char’ Simple2.hs:21:10: warning: [-Wmissing-methods (in -Wdefault)] @@ -9,7 +9,7 @@ Simple2.hs:21:10: warning: [-Wmissing-methods (in -Wdefault)] • In the instance declaration for ‘C3 Char’ Simple2.hs:29:1: warning: [-Wmissing-methods (in -Wdefault)] - • No explicit associated type or default declaration for ‘S3n’ + • No explicit associated type or default declaration for ‘S3n’ • In the instance declaration for ‘C3 Bool’ Simple2.hs:29:10: warning: [-Wmissing-methods (in -Wdefault)] @@ -18,11 +18,11 @@ Simple2.hs:29:10: warning: [-Wmissing-methods (in -Wdefault)] • In the instance declaration for ‘C3 Bool’ Simple2.hs:39:1: warning: [-Wmissing-methods (in -Wdefault)] - • No explicit associated type or default declaration for ‘S3’ + • No explicit associated type or default declaration for ‘S3’ • In the instance declaration for ‘C3 Float’ Simple2.hs:39:1: warning: [-Wmissing-methods (in -Wdefault)] - • No explicit associated type or default declaration for ‘S3n’ + • No explicit associated type or default declaration for ‘S3n’ • In the instance declaration for ‘C3 Float’ Simple2.hs:39:10: warning: [-Wmissing-methods (in -Wdefault)] diff --git a/testsuite/tests/typecheck/should_compile/tc254.stderr b/testsuite/tests/typecheck/should_compile/tc254.stderr index 663279d..2d2c20d 100644 --- a/testsuite/tests/typecheck/should_compile/tc254.stderr +++ b/testsuite/tests/typecheck/should_compile/tc254.stderr @@ -1,4 +1,4 @@ tc254.hs:8:1: warning: [-Wmissing-methods (in -Wdefault)] - • No explicit associated type or default declaration for ‘Typ’ + • No explicit associated type or default declaration for ‘Typ’ • In the instance declaration for ‘Cls Int’ From git at git.haskell.org Thu Jul 13 00:28:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Jul 2017 00:28:36 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: ONLY_PERF_TESTS=YES now fully implemented (b33645e) Message-ID: <20170713002836.59FD73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/b33645ee01d1e277fa848819261ba8a04ca3db57/ghc >--------------------------------------------------------------- commit b33645ee01d1e277fa848819261ba8a04ca3db57 Author: Jared Weakly Date: Wed Jul 12 17:30:31 2017 -0700 ONLY_PERF_TESTS=YES now fully implemented >--------------------------------------------------------------- b33645ee01d1e277fa848819261ba8a04ca3db57 testsuite/driver/runtests.py | 2 ++ testsuite/driver/testlib.py | 1 + 2 files changed, 3 insertions(+) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index c09b063..996dae1 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -337,6 +337,8 @@ else: sys.stdout.flush() summary(t, sys.stdout, config.no_print_summary) + print("Only perf tests: " + str(config.only_perf_tests) + "\n") + print("Skip perf tests: " + str(config.skip_perf_tests) + "\n") if config.summary_file != '': with open(config.summary_file, 'w') as file: diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 887cfe5..8657a12 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -714,6 +714,7 @@ def test_common_work(watcher, name, opts, func, args): and (getTestOpts().only_ways == None or way in getTestOpts().only_ways) \ and (config.cmdline_ways == [] or way in config.cmdline_ways) \ and (not (config.skip_perf_tests and isStatsTest())) \ + and (not (config.only_perf_tests and (not isStatsTest()))) \ and way not in getTestOpts().omit_ways # Which ways we are asked to skip From git at git.haskell.org Thu Jul 13 20:07:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Jul 2017 20:07:19 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] Temporarily disable split-sections on Windows. (f656fba) Message-ID: <20170713200719.2FBD23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f656fba19d0cefe05643ddea35d080ea332a6584/ghc >--------------------------------------------------------------- commit f656fba19d0cefe05643ddea35d080ea332a6584 Author: Tamar Christina Date: Thu Jul 13 21:06:49 2017 +0100 [skip ci] Temporarily disable split-sections on Windows. Summary: This temporarily disabled split-sections again on Windows because of the overhead in linking it introduces. Unfortunately because BFD is so slow a testsuite run gets almost 2x slower. Simply linking Hello World takes an unacceptable long time. So for now, it'll be disabled as we look into different linkers such as LLD. Test Plan: ./validate Reviewers: austin, bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #12913 Differential Revision: https://phabricator.haskell.org/D3731 >--------------------------------------------------------------- f656fba19d0cefe05643ddea35d080ea332a6584 mk/config.mk.in | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index 88f3b51..2e920ca 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -357,8 +357,9 @@ SplitObjs = $(if $(and $(filter YES,$(SupportsSplitObjs)),\ # Set SplitSections=YES or NO in your build.mk to override the default. # # This is not supported on Darwin (where you can use subsections-via-symbols -# instead) and Windows is not yet working. (See #11445 and related tickets.) -OsSupportsSplitSections=$(if $(filter $(TargetOS_CPP),darwin),NO,YES) +# instead) and Windows is disabled until we figure the linking performance +# issues related to BFD out. (See #11445, #12913 and related tickets.) +OsSupportsSplitSections=$(if $(filter $(TargetOS_CPP),mingw32 darwin),NO,YES) SupportsSplitSections=$(if $(and $(filter YES,$(OsSupportsSplitSections)),\ $(filter YES,$(LdIsGNULd))),YES,NO) SplitSections ?= $(SupportsSplitSections) From git at git.haskell.org Tue Jul 18 09:16:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 09:16:42 +0000 (UTC) Subject: [commit: ghc] branch 'wip/zyla-T8095' created Message-ID: <20170718091642.EF9463A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/zyla-T8095 Referencing: bfc9fc95fd7939716b4762ebdb582d723e2b91b1 From git at git.haskell.org Tue Jul 18 09:16:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 09:16:46 +0000 (UTC) Subject: [commit: ghc] wip/zyla-T8095: Add -fomit-type-family-coercions (bfc9fc9) Message-ID: <20170718091646.C63353A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/zyla-T8095 Link : http://ghc.haskell.org/trac/ghc/changeset/bfc9fc95fd7939716b4762ebdb582d723e2b91b1/ghc >--------------------------------------------------------------- commit bfc9fc95fd7939716b4762ebdb582d723e2b91b1 Author: Matthew Pickering Date: Tue Jul 18 09:13:54 2017 +0000 Add -fomit-type-family-coercions Summary: Type family reduction creates a long chain of coercions witnessing the reduction sequence and intermediate types. This leads to long compile times and high memory usage. `-fomit-type-family-coercions` causes GHC to replace coercions coming from `flatten_fam_app` with `UnivCo`. TODO: - Introduce `OmittedProv` instead os just using `UnsafeCoerceProv` - Document the flag Test Plan: make TEST=OmitTyFamCoercions test It may also be beneficial to run the whole test suite with `-fomit-type-family-coercions`. Reviewers: austin, bgamari Subscribers: rwbarton, thomie Tags: #ghc GHC Trac Issues: #8095 Differential Revision: https://phabricator.haskell.org/D3752 >--------------------------------------------------------------- bfc9fc95fd7939716b4762ebdb582d723e2b91b1 compiler/main/DynFlags.hs | 3 + compiler/typecheck/TcFlatten.hs | 17 ++- .../typecheck/should_compile/OmitTyFamCoercions.hs | 14 +++ .../should_compile/OmitTyFamCoercions.stderr | 126 +++++++++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + utils/mkUserGuidePart/Options/Language.hs | 7 ++ 6 files changed, 163 insertions(+), 5 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 bfc9fc95fd7939716b4762ebdb582d723e2b91b1 From git at git.haskell.org Tue Jul 18 11:46:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 11:46:15 +0000 (UTC) Subject: [commit: ghc] master: Fix a missing getNewNursery(), and related cleanup (12ae1fa) Message-ID: <20170718114615.A50EF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/12ae1fa51b2f59e37d6100359b494bee2192ef0a/ghc >--------------------------------------------------------------- commit 12ae1fa51b2f59e37d6100359b494bee2192ef0a Author: Simon Marlow Date: Mon Jul 17 17:32:44 2017 +0100 Fix a missing getNewNursery(), and related cleanup Summary: When we use nursery chunks with +RTS -n, when the current nursery runs out we have to check whether there's another chunk available with getNewNursery(). There was one place we weren't doing this: the ad-hoc heap check in scheduleProcessInbox(). The impact of the bug was that we would GC too early when using nursery chunks, especially in programs that used messages (throwTo between capabilities could do this, also hs_try_putmvar()). Test Plan: validate, also local testing in our application Reviewers: bgamari, niteria, austin, erikd Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3749 >--------------------------------------------------------------- 12ae1fa51b2f59e37d6100359b494bee2192ef0a rts/Schedule.c | 19 +++---------------- rts/sm/Storage.h | 22 +++++++++++----------- 2 files changed, 14 insertions(+), 27 deletions(-) diff --git a/rts/Schedule.c b/rts/Schedule.c index 7950785..8002ac3 100644 --- a/rts/Schedule.c +++ b/rts/Schedule.c @@ -993,8 +993,8 @@ scheduleProcessInbox (Capability **pcap USED_IF_THREADS) Capability *cap = *pcap; while (!emptyInbox(cap)) { - if (cap->r.rCurrentNursery->link == NULL || - g0->n_new_large_words >= large_alloc_lim) { + // Executing messages might use heap, so we should check for GC. + if (doYouWantToGC(cap)) { scheduleDoGC(pcap, cap->running_task, false); cap = *pcap; } @@ -1183,20 +1183,7 @@ scheduleHandleHeapOverflow( Capability *cap, StgTSO *t ) } } - // if we got here because we exceeded large_alloc_lim, then - // proceed straight to GC. - if (g0->n_new_large_words >= large_alloc_lim) { - return true; - } - - // Otherwise, we just ran out of space in the current nursery. - // Grab another nursery if we can. - if (getNewNursery(cap)) { - debugTrace(DEBUG_sched, "thread %ld got a new nursery", t->id); - return false; - } - - return true; + return doYouWantToGC(cap); /* actual GC is done at the end of the while loop in schedule() */ } diff --git a/rts/sm/Storage.h b/rts/sm/Storage.h index 2d69eee..aaa4442 100644 --- a/rts/sm/Storage.h +++ b/rts/sm/Storage.h @@ -25,17 +25,6 @@ void freeStorage(bool free_heap); void storageAddCapabilities (uint32_t from, uint32_t to); /* ----------------------------------------------------------------------------- - Should we GC? - -------------------------------------------------------------------------- */ - -INLINE_HEADER -bool doYouWantToGC(Capability *cap) -{ - return (cap->r.rCurrentNursery->link == NULL || - g0->n_new_large_words >= large_alloc_lim); -} - -/* ----------------------------------------------------------------------------- The storage manager mutex -------------------------------------------------------------------------- */ @@ -75,6 +64,17 @@ StgWord countNurseryBlocks (void); bool getNewNursery (Capability *cap); /* ----------------------------------------------------------------------------- + Should we GC? + -------------------------------------------------------------------------- */ + +INLINE_HEADER +bool doYouWantToGC(Capability *cap) +{ + return ((cap->r.rCurrentNursery->link == NULL && !getNewNursery(cap)) || + g0->n_new_large_words >= large_alloc_lim); +} + +/* ----------------------------------------------------------------------------- Allocation accounting See [Note allocation accounting] in Storage.c From git at git.haskell.org Tue Jul 18 12:11:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 12:11:56 +0000 (UTC) Subject: [commit: ghc] master: Typos in comments and explanation for unusused imports (935acb6) Message-ID: <20170718121156.DA0CC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/935acb6f0de36822b46f8444199dbc37de784af4/ghc >--------------------------------------------------------------- commit 935acb6f0de36822b46f8444199dbc37de784af4 Author: Gabor Greif Date: Mon Jul 17 15:35:59 2017 +0200 Typos in comments and explanation for unusused imports >--------------------------------------------------------------- 935acb6f0de36822b46f8444199dbc37de784af4 compiler/deSugar/DsCCall.hs | 2 +- compiler/rename/RnNames.hs | 4 ++-- compiler/vectorise/Vectorise/Exp.hs | 2 +- libraries/ghci/GHCi/InfoTable.hsc | 10 +++++----- 4 files changed, 9 insertions(+), 9 deletions(-) diff --git a/compiler/deSugar/DsCCall.hs b/compiler/deSugar/DsCCall.hs index b90dd80..2a5769f 100644 --- a/compiler/deSugar/DsCCall.hs +++ b/compiler/deSugar/DsCCall.hs @@ -343,7 +343,7 @@ resultWrapper result_ty -- Data types with a single constructor, which has a single arg -- This includes types like Ptr and ForeignPtr | Just (tycon, tycon_arg_tys) <- maybe_tc_app - , Just data_con <- isDataProductTyCon_maybe tycon -- One construtor, no existentials + , Just data_con <- isDataProductTyCon_maybe tycon -- One constructor, no existentials , [unwrapped_res_ty] <- dataConInstOrigArgTys data_con tycon_arg_tys -- One argument = do { dflags <- getDynFlags ; (maybe_ty, wrapper) <- resultWrapper unwrapped_res_ty diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs index 6dc9f1d..6197bc7 100644 --- a/compiler/rename/RnNames.hs +++ b/compiler/rename/RnNames.hs @@ -762,7 +762,7 @@ The situation is made more complicated by associated types. E.g. Then M's export_avails are (recall the AvailTC invariant from Avails.hs) C(C,T), T(T,T1,T2,T3) Notice that T appears *twice*, once as a child and once as a parent. From -this list we construt a raw list including +this list we construct a raw list including T -> (T, T( T1, T2, T3 ), Nothing) T -> (C, C( C, T ), Nothing) and we combine these (in function 'combine' in 'imp_occ_env' in @@ -1228,7 +1228,7 @@ warnMissingSignatures gbl_env {- Note [The ImportMap] ~~~~~~~~~~~~~~~~~~~~ -The ImportMap is a short-lived intermediate data struture records, for +The ImportMap is a short-lived intermediate data structure records, for each import declaration, what stuff brought into scope by that declaration is actually used in the module. diff --git a/compiler/vectorise/Vectorise/Exp.hs b/compiler/vectorise/Vectorise/Exp.hs index 5ca77b8..f4c1361 100644 --- a/compiler/vectorise/Vectorise/Exp.hs +++ b/compiler/vectorise/Vectorise/Exp.hs @@ -655,7 +655,7 @@ mkScalarFun arg_tys res_ty expr -- In other words, all methods in that dictionary are scalar functions — to be vectorised with -- 'vectScalarFun'. The dictionary "function" itself may be a constant, though. -- --- NB: You may think that we could implement this function guided by the struture of the Core +-- NB: You may think that we could implement this function guided by the structure of the Core -- expression of the right-hand side of the dictionary function. We cannot proceed like this as -- 'vectScalarDFun' must also work for *imported* dfuns, where we don't necessarily have access -- to the Core code of the unvectorised dfun. diff --git a/libraries/ghci/GHCi/InfoTable.hsc b/libraries/ghci/GHCi/InfoTable.hsc index 8a9dfc2..c553897 100644 --- a/libraries/ghci/GHCi/InfoTable.hsc +++ b/libraries/ghci/GHCi/InfoTable.hsc @@ -17,10 +17,10 @@ module GHCi.InfoTable import Data.Maybe (fromJust) #endif import Foreign -import Foreign.C -import GHC.Ptr -import GHC.Exts -import System.IO.Unsafe +import Foreign.C -- needed for 2nd stage +import GHC.Ptr -- needed for 2nd stage +import GHC.Exts -- needed for 2nd stage +import System.IO.Unsafe -- needed for 2nd stage type ItblCodes = Either [Word8] [Word32] @@ -33,7 +33,7 @@ type HalfWord = Word32 #elif SIZEOF_VOID_P == 4 type HalfWord = Word16 #else -#error Uknown SIZEOF_VOID_P +#error Unknown SIZEOF_VOID_P #endif type EntryFunPtr = FunPtr (Ptr () -> IO (Ptr ())) From git at git.haskell.org Tue Jul 18 12:27:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 12:27:38 +0000 (UTC) Subject: [commit: ghc] master: Make module membership on ModuleGraph faster (b8fec69) Message-ID: <20170718122738.7F17B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b8fec6950ad99cbf11cd22698b8d5ab35afb828f/ghc >--------------------------------------------------------------- commit b8fec6950ad99cbf11cd22698b8d5ab35afb828f Author: Bartosz Nitka Date: Wed May 31 10:47:03 2017 -0700 Make module membership on ModuleGraph faster When loading/reloading with a large number of modules (>5000) the cost of linear lookups becomes significant. The changes here made `:reload` go from 6s to 1s on my test case. The bottlenecks were `needsLinker` in `DriverPipeline` and `getModLoop` in `GhcMake`. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Subscribers: thomie, rwbarton Differential Revision: https://phabricator.haskell.org/D3703 >--------------------------------------------------------------- b8fec6950ad99cbf11cd22698b8d5ab35afb828f compiler/backpack/DriverBkp.hs | 5 +- compiler/basicTypes/Module.hs | 5 +- compiler/main/DriverMkDepend.hs | 16 +++--- compiler/main/DriverPipeline.hs | 5 +- compiler/main/GHC.hs | 12 +++-- compiler/main/GhcMake.hs | 73 ++++++++++++++++++--------- compiler/main/HscMain.hs | 2 +- compiler/main/HscTypes.hs | 67 ++++++++++++++++++++---- ghc/GHCi/UI.hs | 23 +++++---- ghc/GHCi/UI/Tags.hs | 2 +- testsuite/tests/ghc-api/apirecomp001/myghc.hs | 4 +- utils/check-api-annotations/Main.hs | 10 ++-- utils/check-ppr/Main.hs | 2 +- utils/ghctags/Main.hs | 6 +-- 14 files changed, 158 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 b8fec6950ad99cbf11cd22698b8d5ab35afb828f From git at git.haskell.org Tue Jul 18 18:36:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 18:36:38 +0000 (UTC) Subject: [commit: ghc] wip/rae: Improve error messages around kind mismatches. (9ed7c68) Message-ID: <20170718183638.3A2A53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/9ed7c68747a86380aeaf23c41edd07d72680d6ef/ghc >--------------------------------------------------------------- commit 9ed7c68747a86380aeaf23c41edd07d72680d6ef Author: Richard Eisenberg Date: Thu Jun 1 17:27:14 2017 -0400 Improve error messages around kind mismatches. Previously, when canonicalizing (or unifying, in uType) a heterogeneous equality, we emitted a kind equality and used the resulting coercion to cast one side of the heterogeneous equality. While sound, this led to terrible error messages. (See the bugs listed below.) The problem is that using the coercion built from the emitted kind equality is a bit like a wanted rewriting a wanted. The solution is to keep heterogeneous equalities as irreducible. See Note [Equalities with incompatible kinds] in TcCanonical. This commit also removes a highly suspicious switch to FM_SubstOnly when flattening in the kinds of a type variable. I have no idea why this was there, other than as a holdover from pre-TypeInType. I've not left a Note because there is simply no reason I can conceive of that the FM_SubstOnly should be there. One challenge with this patch is that the emitted derived equalities might get emitted several times: when a heterogeneous equality is in an implication and then gets floated out from the implication, the Derived is present both in and out of the implication. This causes a duplicate error message. (Test case: typecheck/should_fail/T7368) Solution: track the provenance of Derived constraints and refuse to float out a constraint that has an insoluble Derived. Lastly, this labels one test (dependent/should_fail/RAE_T32a) as expect_broken, because the problem is really #12919. The different handling of constraints in this patch exposes the error. This fixes bugs #11198, #12373, #13530, and #13610. test cases: typecheck/should_fail/{T8262,T8603,tcail122,T12373,T13530,T13610} >--------------------------------------------------------------- 9ed7c68747a86380aeaf23c41edd07d72680d6ef compiler/typecheck/TcCanonical.hs | 296 ++++++++++++--------- compiler/typecheck/TcErrors.hs | 75 ++++-- compiler/typecheck/TcEvidence.hs | 8 +- compiler/typecheck/TcFlatten.hs | 31 ++- compiler/typecheck/TcRnMonad.hs | 16 +- compiler/typecheck/TcRnTypes.hs | 38 ++- compiler/typecheck/TcSimplify.hs | 32 ++- compiler/typecheck/TcType.hs | 10 +- compiler/typecheck/TcUnify.hs | 28 +- compiler/types/Type.hs | 4 +- testsuite/tests/dependent/should_fail/T11471.hs | 2 +- .../tests/dependent/should_fail/T11471.stderr | 11 +- testsuite/tests/dependent/should_fail/all.T | 2 +- testsuite/tests/gadt/gadt7.stderr | 6 +- .../tests/ghci.debugger/scripts/break012.stdout | 14 +- .../indexed-types/should_fail/ExtraTcsUntch.stderr | 6 +- testsuite/tests/polykinds/T12593.stderr | 56 ++++ testsuite/tests/polykinds/T13555.stderr | 21 +- testsuite/tests/polykinds/T7438.stderr | 6 +- testsuite/tests/polykinds/T8566.stderr | 2 +- testsuite/tests/polykinds/T9017.stderr | 10 +- testsuite/tests/typecheck/should_fail/T12373.hs | 10 + .../tests/typecheck/should_fail/T12373.stderr | 8 + testsuite/tests/typecheck/should_fail/T13530.hs | 11 + .../tests/typecheck/should_fail/T13530.stderr | 7 + testsuite/tests/typecheck/should_fail/T13610.hs | 11 + .../tests/typecheck/should_fail/T13610.stderr | 14 + testsuite/tests/typecheck/should_fail/T5691.stderr | 10 +- testsuite/tests/typecheck/should_fail/T7368.stderr | 6 +- .../tests/typecheck/should_fail/T7368a.stderr | 2 +- testsuite/tests/typecheck/should_fail/T7453.stderr | 56 ++-- testsuite/tests/typecheck/should_fail/T7696.stderr | 4 +- testsuite/tests/typecheck/should_fail/T8262.stderr | 6 +- testsuite/tests/typecheck/should_fail/T8603.hs | 4 + testsuite/tests/typecheck/should_fail/T8603.stderr | 13 +- testsuite/tests/typecheck/should_fail/all.T | 3 + .../tests/typecheck/should_fail/tcfail090.stderr | 4 +- .../tests/typecheck/should_fail/tcfail122.stderr | 8 +- .../tests/typecheck/should_fail/tcfail123.stderr | 13 +- .../tests/typecheck/should_fail/tcfail200.stderr | 6 +- 40 files changed, 555 insertions(+), 315 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 9ed7c68747a86380aeaf23c41edd07d72680d6ef From git at git.haskell.org Tue Jul 18 18:36:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 18:36:41 +0000 (UTC) Subject: [commit: ghc] wip/rae: Don't tidy vars when dumping a type (86e1984) Message-ID: <20170718183641.0228B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/86e1984241765e377270bc88886e0a427081c56c/ghc >--------------------------------------------------------------- commit 86e1984241765e377270bc88886e0a427081c56c Author: Richard Eisenberg Date: Fri Apr 7 11:13:32 2017 -0400 Don't tidy vars when dumping a type This makes variables print more consistenty in, say, -ddump-tc-trace. >--------------------------------------------------------------- 86e1984241765e377270bc88886e0a427081c56c compiler/types/TyCoRep.hs | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index e6afece..a93d13e 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -137,8 +137,8 @@ import {-# SOURCE #-} DataCon( dataConFullSig , dataConUnivTyVarBinders, dataConExTyVarBinders , DataCon, filterEqSpec ) import {-# SOURCE #-} Type( isPredTy, isCoercionTy, mkAppTy, mkCastTy - , tyCoVarsOfTypesWellScoped , tyCoVarsOfTypeWellScoped + , tyCoVarsOfTypesWellScoped , coreView, typeKind ) -- Transitively pulls in a LOT of stuff, better to break the loop @@ -2435,7 +2435,7 @@ pprType = pprPrecType TopPrec pprParendType = pprPrecType TyConPrec pprPrecType :: TyPrec -> Type -> SDoc -pprPrecType prec ty = pprPrecIfaceType prec (tidyToIfaceType ty) +pprPrecType prec ty = getPprStyle $ \sty -> pprPrecIfaceType prec (tidyToIfaceTypeSty ty sty) pprTyLit :: TyLit -> SDoc pprTyLit = pprIfaceTyLit . toIfaceTyLit @@ -2444,6 +2444,12 @@ pprKind, pprParendKind :: Kind -> SDoc pprKind = pprType pprParendKind = pprParendType +tidyToIfaceTypeSty :: Type -> PprStyle -> IfaceType +tidyToIfaceTypeSty ty sty + | userStyle sty = tidyToIfaceType ty + | otherwise = toIfaceTypeX (tyCoVarsOfType ty) ty + -- in latter case, don't tidy, as we'll be printing uniques. + tidyToIfaceType :: Type -> IfaceType -- It's vital to tidy before converting to an IfaceType -- or nested binders will become indistinguishable! From git at git.haskell.org Tue Jul 18 18:36:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 18:36:43 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #11400, #11560 by documenting an infelicity. (a82cc35) Message-ID: <20170718183643.B3D813A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/a82cc35e52dde3c81ee6e8b7b2dc5e670d0eecc3/ghc >--------------------------------------------------------------- commit a82cc35e52dde3c81ee6e8b7b2dc5e670d0eecc3 Author: Richard Eisenberg Date: Thu Jun 1 18:09:05 2017 -0400 Fix #11400, #11560 by documenting an infelicity. Really, the fix for both of these is #11307. >--------------------------------------------------------------- a82cc35e52dde3c81ee6e8b7b2dc5e670d0eecc3 docs/users_guide/glasgow_exts.rst | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index e4da54e..336a907 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -8296,9 +8296,9 @@ enabled). The only way ``*`` is unordinary is in its parsing. In order to be backward compatible, ``*`` is parsed as if it were an alphanumeric idenfifier; note that we do not write ``Int :: (*)`` but just plain ``Int :: *``. Due to the -bizarreness with which ``*`` is parsed-and the fact that it is the only such -operator in GHC-there are some corner cases that are -not handled. We are aware of two: +bizarreness with which ``*`` is parsed--and the fact that it is the only such +operator in GHC--there are some corner cases that are +not handled. We are aware of three: - In a Haskell-98-style data constructor, you must put parentheses around ``*``, like this: :: @@ -8312,6 +8312,10 @@ not handled. We are aware of two: Note that the keyword ``type`` there is just to disambiguate the import from a term-level ``(*)``. (:ref:`explicit-namespaces`) +- In an instance declaration head (the part after the word ``instance``), you + must parenthesize ``*``. This applies to all manners of instances, including + the left-hand sides of individual equations of a closed type family. + The ``Data.Kind`` module also exports ``Type`` as a synonym for ``*``. Now that type synonyms work in kinds, it is conceivable that we will deprecate ``*`` when there is a good migration story for everyone to use ``Type``. From git at git.haskell.org Tue Jul 18 18:36:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 18:36:46 +0000 (UTC) Subject: [commit: ghc] wip/rae: Preserve CoVar uniques during pretty printing (9c7ee19) Message-ID: <20170718183646.762203A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/9c7ee1925e585b6e38b6e224ac0995ab54067e2b/ghc >--------------------------------------------------------------- commit 9c7ee1925e585b6e38b6e224ac0995ab54067e2b Author: Richard Eisenberg Date: Tue Jun 6 10:07:16 2017 -0400 Preserve CoVar uniques during pretty printing Previously, we did this for Types, but not for Coercions. >--------------------------------------------------------------- 9c7ee1925e585b6e38b6e224ac0995ab54067e2b compiler/backpack/RnModIface.hs | 1 + compiler/iface/IfaceSyn.hs | 1 + compiler/iface/IfaceType.hs | 9 ++++++++- compiler/iface/TcIface.hs | 1 + compiler/iface/ToIface.hs | 8 +++++--- testsuite/tests/roles/should_compile/Roles13.stderr | 2 +- 6 files changed, 17 insertions(+), 5 deletions(-) diff --git a/compiler/backpack/RnModIface.hs b/compiler/backpack/RnModIface.hs index 2e738c1..e3da067 100644 --- a/compiler/backpack/RnModIface.hs +++ b/compiler/backpack/RnModIface.hs @@ -646,6 +646,7 @@ rnIfaceCo (IfaceAppCo co1 co2) = IfaceAppCo <$> rnIfaceCo co1 <*> rnIfaceCo co2 rnIfaceCo (IfaceForAllCo bndr co1 co2) = IfaceForAllCo <$> rnIfaceTvBndr bndr <*> rnIfaceCo co1 <*> rnIfaceCo co2 +rnIfaceCo (IfaceFreeCoVar c) = pure (IfaceFreeCoVar c) rnIfaceCo (IfaceCoVarCo lcl) = IfaceCoVarCo <$> pure lcl rnIfaceCo (IfaceAxiomInstCo n i cs) = IfaceAxiomInstCo <$> rnIfaceGlobal n <*> pure i <*> mapM rnIfaceCo cs diff --git a/compiler/iface/IfaceSyn.hs b/compiler/iface/IfaceSyn.hs index 60206ea..3360d74 100644 --- a/compiler/iface/IfaceSyn.hs +++ b/compiler/iface/IfaceSyn.hs @@ -1424,6 +1424,7 @@ freeNamesIfCoercion (IfaceAppCo c1 c2) = freeNamesIfCoercion c1 &&& freeNamesIfCoercion c2 freeNamesIfCoercion (IfaceForAllCo _ kind_co co) = freeNamesIfCoercion kind_co &&& freeNamesIfCoercion co +freeNamesIfCoercion (IfaceFreeCoVar _) = emptyNameSet freeNamesIfCoercion (IfaceCoVarCo _) = emptyNameSet freeNamesIfCoercion (IfaceAxiomInstCo ax _ cos) diff --git a/compiler/iface/IfaceType.hs b/compiler/iface/IfaceType.hs index 39e3028..4ab40d4 100644 --- a/compiler/iface/IfaceType.hs +++ b/compiler/iface/IfaceType.hs @@ -109,7 +109,7 @@ data IfaceOneShot -- See Note [Preserve OneShotInfo] in CoreTicy type IfaceKind = IfaceType data IfaceType -- A kind of universal type, used for types and kinds - = IfaceFreeTyVar TyVar -- See Note [Free tyvars in IfaceType] + = IfaceFreeTyVar TyVar -- See Note [Free tyvars in IfaceType] | IfaceTyVar IfLclName -- Type/coercion variable only, not tycon | IfaceLitTy IfaceTyLit | IfaceAppTy IfaceType IfaceType @@ -204,6 +204,7 @@ Note that: to deserialise one. IfaceFreeTyVar is used only in the "convert to IfaceType and then pretty-print" pipeline. +We do the same for covars, naturally. Note [Equality predicates in IfaceType] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -242,6 +243,7 @@ data IfaceCoercion | IfaceTyConAppCo Role IfaceTyCon [IfaceCoercion] | IfaceAppCo IfaceCoercion IfaceCoercion | IfaceForAllCo IfaceTvBndr IfaceCoercion IfaceCoercion + | IfaceFreeCoVar CoVar -- See Note [Free tyvars in IfaceType] | IfaceCoVarCo IfLclName | IfaceAxiomInstCo IfExtName BranchIndex [IfaceCoercion] | IfaceUnivCo IfaceUnivCoProv Role IfaceType IfaceType @@ -395,6 +397,7 @@ substIfaceType env ty go_co (IfaceTyConAppCo r tc cos) = IfaceTyConAppCo r tc (go_cos cos) go_co (IfaceAppCo c1 c2) = IfaceAppCo (go_co c1) (go_co c2) go_co (IfaceForAllCo {}) = pprPanic "substIfaceCoercion" (ppr ty) + go_co (IfaceFreeCoVar cv) = IfaceFreeCoVar cv go_co (IfaceCoVarCo cv) = IfaceCoVarCo cv go_co (IfaceAxiomInstCo a i cos) = IfaceAxiomInstCo a i (go_cos cos) go_co (IfaceUnivCo prov r t1 t2) = IfaceUnivCo (go_prov prov) r (go t1) (go t2) @@ -1039,6 +1042,8 @@ ppr_co ctxt_prec co@(IfaceForAllCo {}) = let (tvs, co'') = split_co co' in ((name,kind_co):tvs,co'') split_co co' = ([], co') +-- Why these two? See Note [TcTyVars in IfaceType] +ppr_co _ (IfaceFreeCoVar covar) = ppr covar ppr_co _ (IfaceCoVarCo covar) = ppr covar ppr_co ctxt_prec (IfaceUnivCo IfaceUnsafeCoerceProv r ty1 ty2) @@ -1321,6 +1326,8 @@ instance Binary IfaceCoercion where put_ bh a put_ bh b put_ bh c + put_ _ (IfaceFreeCoVar cv) + = pprPanic "Can't serialise IfaceFreeCoVar" (ppr cv) put_ bh (IfaceCoVarCo a) = do putByte bh 6 put_ bh a diff --git a/compiler/iface/TcIface.hs b/compiler/iface/TcIface.hs index 3a6a407..f677935 100644 --- a/compiler/iface/TcIface.hs +++ b/compiler/iface/TcIface.hs @@ -1314,6 +1314,7 @@ tcIfaceCo = go go (IfaceForAllCo tv k c) = do { k' <- go k ; bindIfaceTyVar tv $ \ tv' -> ForAllCo tv' k' <$> go c } + go (IfaceFreeCoVar c) = pprPanic "tcIfaceCo:IfaceFreeCoVar" (ppr c) go (IfaceCoVarCo n) = CoVarCo <$> go_var n go (IfaceAxiomInstCo n i cs) = AxiomInstCo <$> tcIfaceCoAxiom n <*> pure i <*> mapM go cs go (IfaceUnivCo p r t1 t2) = UnivCo <$> tcIfaceUnivCoProv p <*> pure r diff --git a/compiler/iface/ToIface.hs b/compiler/iface/ToIface.hs index 59184dc..ce956c8 100644 --- a/compiler/iface/ToIface.hs +++ b/compiler/iface/ToIface.hs @@ -217,7 +217,10 @@ toIfaceCoercionX fr co = go co where go (Refl r ty) = IfaceReflCo r (toIfaceType ty) - go (CoVarCo cv) = IfaceCoVarCo (toIfaceCoVar cv) + go (CoVarCo cv) + -- See [TcTyVars in IfaceType] in IfaceType + | cv `elemVarSet` fr = IfaceFreeCoVar cv + | otherwise = IfaceCoVarCo (toIfaceCoVar cv) go (AppCo co1 co2) = IfaceAppCo (go co1) (go co2) go (SymCo co) = IfaceSymCo (go co) go (TransCo co1 co2) = IfaceTransCo (go co1) (go co2) @@ -236,8 +239,7 @@ toIfaceCoercionX fr co | tc `hasKey` funTyConKey , [_,_,_,_] <- cos = pprPanic "toIfaceCoercion" (ppr co) | otherwise = IfaceTyConAppCo r (toIfaceTyCon tc) (map go cos) - go (FunCo r co1 co2) = IfaceFunCo r (toIfaceCoercion co1) - (toIfaceCoercion co2) + go (FunCo r co1 co2) = IfaceFunCo r (go co1) (go co2) go (ForAllCo tv k co) = IfaceForAllCo (toIfaceTvBndr tv) (toIfaceCoercionX fr' k) diff --git a/testsuite/tests/roles/should_compile/Roles13.stderr b/testsuite/tests/roles/should_compile/Roles13.stderr index f4b44a2..414ef80 100644 --- a/testsuite/tests/roles/should_compile/Roles13.stderr +++ b/testsuite/tests/roles/should_compile/Roles13.stderr @@ -13,7 +13,7 @@ convert :: Wrap Age -> Int [GblId, Arity=1, Caf=NoCafRefs] convert = convert1 - `cast` (_R -> Roles13.N:Wrap[0] Roles13.N:Age[0] + `cast` (_R ->_R Roles13.N:Wrap[0] (Roles13.N:Age[0]) :: (Wrap Age -> Wrap Age :: *) ~R# (Wrap Age -> Int :: *)) -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} From git at git.haskell.org Tue Jul 18 18:36:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 18:36:50 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #11672 in typecheck/should_fail/T11672. (0ab271d) Message-ID: <20170718183650.19EC93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/0ab271ddb85773d4fb394e41f606d997d823fc22/ghc >--------------------------------------------------------------- commit 0ab271ddb85773d4fb394e41f606d997d823fc22 Author: Richard Eisenberg Date: Thu Jun 1 18:28:57 2017 -0400 Test #11672 in typecheck/should_fail/T11672. I believe this was fixed with the fix for #11198. >--------------------------------------------------------------- 0ab271ddb85773d4fb394e41f606d997d823fc22 testsuite/tests/typecheck/should_fail/T11672.hs | 9 +++++++++ testsuite/tests/typecheck/should_fail/T11672.stderr | 21 +++++++++++++++++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 31 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T11672.hs b/testsuite/tests/typecheck/should_fail/T11672.hs new file mode 100644 index 0000000..8c5e2fb --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T11672.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE KindSignatures #-} +module BadError where + +import GHC.TypeLits +import Data.Proxy + +f :: Proxy (a :: Symbol) -> Int +f _ = f (Proxy :: Proxy (Int -> Bool)) diff --git a/testsuite/tests/typecheck/should_fail/T11672.stderr b/testsuite/tests/typecheck/should_fail/T11672.stderr new file mode 100644 index 0000000..d08acba --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T11672.stderr @@ -0,0 +1,21 @@ + +T11672.hs:9:10: error: + • Couldn't match kind ‘Symbol’ with ‘*’ + When matching types + a0 :: Symbol + Int -> Bool :: * + Expected type: Proxy a0 + Actual type: Proxy (Int -> Bool) + • In the first argument of ‘f’, namely + ‘(Proxy :: Proxy (Int -> Bool))’ + In the expression: f (Proxy :: Proxy (Int -> Bool)) + In an equation for ‘f’: f _ = f (Proxy :: Proxy (Int -> Bool)) + +T11672.hs:9:10: error: + • Couldn't match type ‘*’ with ‘Symbol’ + Expected type: Proxy a0 + Actual type: Proxy (Int -> Bool) + • In the first argument of ‘f’, namely + ‘(Proxy :: Proxy (Int -> Bool))’ + In the expression: f (Proxy :: Proxy (Int -> Bool)) + In an equation for ‘f’: f _ = f (Proxy :: Proxy (Int -> Bool)) diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index d5cfc8a..7447783 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -445,3 +445,4 @@ test('T13677', normal, compile_fail, ['']) test('T13530', normal, compile_fail, ['']) test('T12373', normal, compile_fail, ['']) test('T13610', normal, compile_fail, ['']) +test('T11672', normal, compile_fail, ['']) From git at git.haskell.org Tue Jul 18 18:36:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 18:36:54 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #13819 by refactoring TypeEqOrigin.uo_thing (8aababe) Message-ID: <20170718183654.0EABE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/8aababe96861af9fc33beb84546aaef70689de62/ghc >--------------------------------------------------------------- commit 8aababe96861af9fc33beb84546aaef70689de62 Author: Richard Eisenberg Date: Wed Jun 14 16:35:18 2017 -0400 Fix #13819 by refactoring TypeEqOrigin.uo_thing The uo_thing field of TypeEqOrigin is used to track the "thing" (either term or type) that has the type (kind) stored in the TypeEqOrigin fields. Previously, this was sometimes a proper Core Type, which needed zonking and tidying. Now, it is only HsSyn: much simpler, and the error messages now use the user-written syntax. But this aspect of uo_thing didn't cause #13819; it was the sibling field uo_arity that did. uo_arity stored the number of arguments of uo_thing, useful when reporting something like "should have written 2 fewer arguments". We wouldn't want to say that if the thing didn't have two arguments. However, in practice, GHC was getting this wrong, and this message didn't seem all that helpful. Furthermore, the calculation of the number of arguments is what caused #13819 to fall over. This patch just removes uo_arity. In my opinion, the change to error messages is a nudge in the right direction. Test case: typecheck/should_fail/T13819 >--------------------------------------------------------------- 8aababe96861af9fc33beb84546aaef70689de62 compiler/ghci/RtClosureInspect.hs | 4 +- compiler/typecheck/Inst.hs | 8 +- compiler/typecheck/TcArrows.hs | 2 +- compiler/typecheck/TcErrors.hs | 20 ++- compiler/typecheck/TcExpr.hs | 50 ++++---- compiler/typecheck/TcHsType.hs | 135 +++++++++++---------- compiler/typecheck/TcMType.hs | 30 +---- compiler/typecheck/TcPat.hs | 6 +- compiler/typecheck/TcRnTypes.hs | 21 +--- compiler/typecheck/TcSigs.hs | 4 +- compiler/typecheck/TcSplice.hs | 13 +- compiler/typecheck/TcSplice.hs-boot | 6 +- compiler/typecheck/TcTyClsDecls.hs | 2 +- compiler/typecheck/TcType.hs | 7 ++ compiler/typecheck/TcUnify.hs | 65 +++++----- compiler/typecheck/TcUnify.hs-boot | 7 +- compiler/types/Type.hs | 2 +- .../tests/indexed-types/should_fail/T12867.stderr | 3 +- testsuite/tests/polykinds/T12593.stderr | 7 +- testsuite/tests/polykinds/T6039.stderr | 3 +- testsuite/tests/polykinds/T7278.stderr | 3 +- testsuite/tests/polykinds/T8616.stderr | 2 +- testsuite/tests/polykinds/T9200b.stderr | 6 +- .../tests/rename/should_fail/rnfail026.stderr | 3 +- testsuite/tests/th/T3177a.stderr | 6 +- .../tests/typecheck/should_fail/T11356.stderr | 3 +- .../tests/typecheck/should_fail/T11672.stderr | 11 +- .../tests/typecheck/should_fail/T12785b.stderr | 6 + testsuite/tests/typecheck/should_fail/T13819.hs | 14 +++ .../tests/typecheck/should_fail/T13819.stderr | 18 +++ testsuite/tests/typecheck/should_fail/T2994.stderr | 3 +- testsuite/tests/typecheck/should_fail/T3540.stderr | 2 +- testsuite/tests/typecheck/should_fail/T4875.stderr | 6 +- testsuite/tests/typecheck/should_fail/T7609.stderr | 11 +- testsuite/tests/typecheck/should_fail/T7778.stderr | 10 +- testsuite/tests/typecheck/should_fail/all.T | 1 + .../tests/typecheck/should_fail/tcfail070.stderr | 3 +- .../tests/typecheck/should_fail/tcfail078.stderr | 6 +- .../tests/typecheck/should_fail/tcfail113.stderr | 12 +- .../tests/typecheck/should_fail/tcfail123.stderr | 9 -- .../tests/typecheck/should_fail/tcfail132.stderr | 3 +- 41 files changed, 243 insertions(+), 290 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 8aababe96861af9fc33beb84546aaef70689de62 From git at git.haskell.org Tue Jul 18 18:36:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 18:36:56 +0000 (UTC) Subject: [commit: ghc] wip/rae: Track visibility in TypeEqOrigin (cbf1af5) Message-ID: <20170718183656.CE6BE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/cbf1af59f8c9884967cc5b33b21a327780f32427/ghc >--------------------------------------------------------------- commit cbf1af59f8c9884967cc5b33b21a327780f32427 Author: Richard Eisenberg Date: Tue Jul 18 14:30:40 2017 -0400 Track visibility in TypeEqOrigin A type equality error can arise from a mismatch between *invisible* arguments just as easily as from visible arguments. But we should really prefer printing out errors from visible arguments over invisible ones. Suppose we have a mismatch between `Proxy Int` and `Proxy Maybe`. Would you rather get an error between `Int` and `Maybe`? Or between `*` and `* -> *`? I thought so, too. There is a fair amount of plumbing with this one, but I think it's worth it. >--------------------------------------------------------------- cbf1af59f8c9884967cc5b33b21a327780f32427 compiler/typecheck/Inst.hs | 3 +- compiler/typecheck/TcCanonical.hs | 18 +++-- compiler/typecheck/TcErrors.hs | 29 ++++---- compiler/typecheck/TcHsType.hs | 5 +- compiler/typecheck/TcRnTypes.hs | 30 ++++++++- compiler/typecheck/TcType.hs | 38 ++++++++++- compiler/typecheck/TcUnify.hs | 78 +++++++++++++--------- testsuite/tests/polykinds/KindVType.stderr | 2 +- .../tests/typecheck/should_fail/T12373.stderr | 3 + .../tests/typecheck/should_fail/T13530.stderr | 3 + testsuite/tests/typecheck/should_fail/T8603.stderr | 7 +- 11 files changed, 150 insertions(+), 66 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 cbf1af59f8c9884967cc5b33b21a327780f32427 From git at git.haskell.org Tue Jul 18 18:36:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 18:36:59 +0000 (UTC) Subject: [commit: ghc] wip/rae: Remove old coercion pretty-printer (0b9fb29) Message-ID: <20170718183659.922DA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/0b9fb2929a445fd450d3dd2bb0a0b36d10720545/ghc >--------------------------------------------------------------- commit 0b9fb2929a445fd450d3dd2bb0a0b36d10720545 Author: Richard Eisenberg Date: Tue Jun 6 11:01:14 2017 -0400 Remove old coercion pretty-printer Now, all coercions are printed from IfaceType, just like types. This also changes the rendering of TransCo to use ; instead of a prefix operator. >--------------------------------------------------------------- 0b9fb2929a445fd450d3dd2bb0a0b36d10720545 compiler/iface/IfaceType.hs | 3 +- compiler/iface/ToIface.hs | 4 +- compiler/iface/ToIface.hs-boot | 2 +- compiler/types/Coercion.hs | 107 +++++----------------------------------- compiler/types/Coercion.hs-boot | 3 -- compiler/types/TyCoRep.hs | 35 ++++++++++--- compiler/types/Type.hs | 2 +- compiler/types/Type.hs-boot | 7 +-- 8 files changed, 49 insertions(+), 114 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 0b9fb2929a445fd450d3dd2bb0a0b36d10720545 From git at git.haskell.org Tue Jul 18 18:37:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 18:37:07 +0000 (UTC) Subject: [commit: ghc] wip/rae's head updated: Track visibility in TypeEqOrigin (cbf1af5) Message-ID: <20170718183707.EDE2A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/rae' now includes: 7fafb84 testsuite/conc059: Don't attempt to use stdcall where it isn't supported 747e77c Fix naming of the native latin1 encodings ddc271e Travis: Add dependency on python3 27731f1 Note Trac #12141 in mk/build.mk.sample f46369b fdReady: use poll() instead of select() 895a131 Install toplevel handler inside fork. 2350906 Maintain in-scope set in deeply_instantiate (fixes #12549). eb6f673 8.2.1-notes.rst: tweak binutils version 90c5af4 core-spec: Fix S_MatchData 517d03e Fix an asymptotic bug in the occurrence analyser 6305674 Fix used-variable calculation (Trac #12548) e912310 Use isFamFreeTyCon now we have it 3e3f7c2 Test Trac #12925 847d229 Color output is wreaking havoc on test results b82f71b Fix x86 Windows build and testsuite eec02ab Give concrete example for #12784 in 8.0.2 release notes 24e6594 Overhaul GC stats 19ae142 Mark rn017 and T7672 as expect_broken(#12930) with -DDEBUG 6e4188a Fix unsafe usage of `is_iloc` selector in Ord instance for ImportSpec eafa06d Revert "Mark rn017 and T7672 as expect_broken(#12930) with -DDEBUG" b7e88ee Reduce the size of string literals in binaries. 41ec722d Test Trac #12919 39143a4 Mark T9577 as broken on Darwin due to #12937 4dd6b37 Really mark T9577 as broken 7036fde Overhaul of Compact Regions (#12455) c02aeb5 Ignore output for compact_gc: sizes change when profiling 5aa9c75 Fix the test with -O 9043a40 Fix crashes in hash table scanning with THREADED_RTS d70d452 rts: Use pthread itimer implementation on Darwin 83d69dc Don't barf() on failures in loadArchive() 499e438 Add HsSyn prettyprinter tests 58d78dc Fix pretty printer test to nog generate stdout 9bcc4e3 Remove stray commented out line in all.T c5fbbac Ignore stderr of all printer tests 62332f3 Setup tcg_imports earlier during signature matching, so orphans are visible. 617d57d Reduce qualification in error messages from signature matching. 58c290a hschooks.c: Fix long line 5063edb arclint: Lint cabal files c766d53 rts/linker: Fix LoadArchive build on Windows 6889400 testsuite: Add test for #10249 1e5b7d7 Update Windows GCC driver. 55361b3 nativeGen: Fix string merging on Windows 2bb099e BlockId: remove BlockMap and BlockSet synonyms 6da6253 rts/PosixSource.h: Define __USE_MINGW_ANSI_STDIO on Windows f65ff2c Disambiguate reified closed type family kinds in TH 61932cd Bump haddock submodule d3b546b Scrutinee Constant Folding cee72d5 Disable colors unless printing to stderr 1c296c0c Export `warningGroups' and `warningHierarchies' 62418b8 Mark T12903 as broken on OS X 90fae01 Fix LLVM TBAA metadata 2823492 NCG: Implement trivColorable for PowerPC 64-bit ca593c7 testsuite: make tests respond to SIGINT properly d1df8d1 Ensure each test inherits the TEST_HC_OPTS 5349d64 Rename TH constructors for deriving strategies 24a4fe2 testsuite: Mark prog003 as broken on Windows 2618090 testsuite: Fix syntax error in rts/all.T 17ac9b1 rts: Provide _lock_file in symbol table on Windows 0ac5a00 Add `_unlock_file` to RTS symbols 490b942 Automate GCC driver wrapper c3c7024 Make globals use sharedCAF 818e027 Refactor pruning of implication constraints f1036ad Make dropDerivedSimples restore [WD] constraints 6720376 Disable T12903 due to flakiness d03dd23 Fix a long-standing bug in CSE bc3d37d Float unboxed expressions by boxing 8f6d241 Add infix flag for class and data declarations 24f6bec Sanity check if we pick up an hsig file without -instantiated-with. db23ccf Fix recompilation detection when set of signatures to merge changes. f723ba2 Revert "Float unboxed expressions by boxing" cc2e3ec base: Make raw buffer IO operations more strict cb582b6 Don't have CPP macros expanding to 'defined'. 9cb4a13 Fix Win32 x86 build validation after D2756 aa123f4 Fix testcase T12903 on OS X 7031704 print * in unicode correctly (fixes #12550) 8ec864d Fix pretty printing of top level SCC pragmas 9c9a222 Load orphan interfaces before checking if module implements signature 26ce99c Fix typo in users' guide 52c5e55 mk/config.mk.in: enable SMP on ARMv7+ (Trac #12981) 0c3341b Show constraints when reporting typed holes 6f7d827 Reset FPU precision back to MSVCRT defaults 8b2e588 Adds llvm-prof flavour 6370a56 Build terminfo on iOS. 3c7cf18 Fix pprCLabel on platforms without native codegen. be5384c testsuite: Mark T9577 as broken due to #12965 27287c8 procPointAnalysis doesn't need UniqSM fe5d68a Add entry to .gitignore to for __.SYMDEF_SORTED 9550b8d Make unboxedTuple{Type,Data}Name support 0- and 1-tuples 2940a61 testsuite: Specify expected allocations of T12877 for Windows 5c76f83 check-ppr: Add a --dump flag to aid in debugging 394231b Fix cost-centre-stacks bug (#5654) 1ec632f Fix pretty printing of MINIMAL signatures 503219e Warn about missing instance methods that start with an underscore d398162 testsuite: Separate out Windows results for T5205 4d683fa base: Bump version to 4.10.0.0 8f0546b testsuite: Add test for #12971 0cad52d testsuite: Mark T10294 as fixed 81c4956 testsuite: Add test for #12966 cd4b202 array: Check for integer overflow during allocation 0d213c1 UniqSupply: Use full range of machine word ffc2327 base: Add more POSIX types (fixes #12795) 6fecb2a Verify that known-key uniques fit in interface file ed4cf03 Typos in comments 13c1fc4 DynFlags: Rip out remnants of WarnContextQuantification c889df8 Packages: Kill unused UnitId argument to isDllName 5bf344b CLabel: Kill redundant UnitId argument from labelDynamic 222e99d Make up a module name for c-- files 4026b45 Fix string merging with -split-sections 8f71d95 Enable split sections by default where possible c8ed1bd testsuite: Add test for #12993 2fa00f5 UNREG: include CCS_OVERHEAD to STG a6657bd revert '-Wl' prefixing to *_LD_OPTS c480860 rts/Compact.cmm: fix UNREG build failure d88efb7 Fix Pretty printer tests on Windows 0af959b Revert "Do not init record accessors as exported" 87c3b1d fix OpenBSD linkage (wxneeded) 6c816c5 utils/genargs: delete unused tool 8906e7b Reshuffle levity polymorphism checks. 3dbd2b0 Windows: Improve terminal detection mechanism 2d1beb1 rts/win32/IOManager: Fix integer types 343b147 Reexport Language.Haskell.TH.Lib from Language.Haskell.TH 2a02040 Fix bug in previous fix for #5654 90cfa84 Run some tests with -fexternal-interpreter -prof 21dde81 Improve StringBuffer and FastString docs e0fe7c3 Docs: Delete duplicate paragraph in user guide 52ba947 Allow use of the external interpreter in stage1. 25b70a2 Check family instance consistency of hs-boot families later, fixes #11062. 630cfc3 Fix Haddock comment typo. b5d788a Introduce unboxedSum{Data,Type}Name to template-haskell 513eb6a Fix #12998 by removing CTimer 88e8194 T12035j: disable on NOSMP targets 4704d65 T8209: disable on NOSMP targets 7f5be7e T10296a: disable on NOSMP targets d327ebd regalloc_unit_tests: disable on UNREG targets bb74bc7 T8242: disable on NOSMP targets f1dfce1 Revert "Allow use of the external interpreter in stage1." 6263e10 Fix timeout's timeout on Windows c0c1f80 Mark T8089 as unbroken since #7325 is now resolved 27f7925 Allow use of the external interpreter in stage1. 4535fa2 Test Trac #12996 8fdb937 Make CompactionFailed a newtype 574abb7 Rewrite Note [Api annotations] for clarity. 9a29b65 Suppress duplicate .T files 1771da2 Fix typos (not test relevant) f97d489 Test Trac #12968, plus some comments c73a982 Add note for rebindable syntax of [a..b] c66dd05 Move typeSize/coercionSize into TyCoRep d250d49 Add INLINE pragamas on Traversable default methods e07ad4d Don't eta-expand in stable unfoldings 0a18231 Lint DFunUnfoldings 05d233e Move InId/OutId to CoreSyn c48595e Never apply worker/wrapper to DFuns 1a4c04b Fix 'SPECIALISE instance' c469db4 Test Trac #12950 74033c4 Improved perf for T12227 ccc918c Fix a forward reference to a Note 2189239 Disambiguate two Notes with identical names ee4e165 Support for abi-depends for computing shadowing. 99db12f Update ghc-cabal command line usage text. 46f7f31 Notes on parsing lists in Parser.y 41ade95 Fix another forward reference to a Note b7a6e62 Revert "Suppress duplicate .T files" efc4a16 Allow timeout to kill entire process tree. 7a13f1f Alpha-renaming and white space only f06b71a Fix a bug in ABot handling in CoreArity ea8f91d White space only 9a4af2c Comments only 11306d6 Ensure that even bottoming functions have an unfolding 432f952 Float unboxed expressions by boxing 793ddb6 Tiny refactor in CoreTidy 75e8c30 Propagate evaluated-ness a bit more faithfully ee872d3 Removed dead code in DsCCall.mk_alt b4c3a66 Push coercions in exprIsConApp_maybe 8712148 testsuite: Split out Windows allocations numbers for T12234 f95e669 users-guide: Kill extraneous link 8f89e76 rename: Don't require 'fail' in non-monadic contexts 158530a Add caret diagnostics 46a195f Use python3 for linters 1b06231 Fix test for T12877 94d2cce base: Override Foldable.{toList,length} for NonEmpty 2689a16 Define MAP_ANONYMOUS on systems that only provide MAP_ANON 48a5da9 rename: Add note describing #11216 9331e33 check-ppr: Make --dump the default behavior 3c9fbba Remove redudant import from check-ppr 815099c CallArity: Use exprIsCheap to detect thunks d2788ab Expand I/O CP in comments 88f5add testsuite: Fix T13025 4dec7d1 Testsuite: Skip failing tests on PowerPC 64-bit f3b99c7 Bump array submodule a370440 Fix various issues with testsuite code on Windows bab4ae8 Fix incorrect statement about plugin packages. 9ff0738 Remove documentation about non-existent flag. c560957 Disallow users to write instances of KnownNat and KnownSym cc0abfa Update .mailmap b28ca38 Don't suggest enabling TypeApplications when it's already enabled 8d63ca9 Refactor importdecls/topdecls parsing. 5800b02 Add specialization rules for realToFrac on Complex 683ed47 Don't use $ in the definition of (<**>) in GHC.Base 6b3c039 Typo in manual [ci skip] df72368 Typofixes in manual and comments [ci skip] 2664641 Remove a redundant test c909e6e Minor refactoring in CSE baf9ebe Ensure nested binders have Internal Names 19d5c73 Add a CSE pass to Stg (#9291) 5d2a92a Use atomic counter for GHC.Event.Unique 5797784 Remove single top-level section in Foldable docs 5ef956e Fix doctests in Data.Functor 5f91ac8 Coerce for fmapDefault and foldMapDefault e6aefd6 Use the right in-scope set 3540d1e Avoid exponential blowup in FamInstEnv.normaliseType b4f2afe Fix the implementation of the "push rules" 5088110 Add performance test for #13056 3a18baf More fixes for #5654 f3c7cf9 Add missing stderr file for T13035 e5d1ed9 Have addModFinalizer expose the local type environment. 54227a4 Actually add the right file for T13035 stderr c5452cc Revert "Have addModFinalizer expose the local type environment." c1ed955 Have addModFinalizer expose the local type environment. 7b317ef TH: Add Trustworthy language pragma 6c869f9 Parse holes as infix operators 7d2e5da Fix zonk_eq_types in TcCanonical a8a714e Typos in comments (and in a test) 1a6bdca Make HsIParamTy have a Located HsIPName e94b07d CmmCommonBlockElim: Ignore CmmUnwind nodes 6fe9b05 Properly detect MinTTY when running GHCi on Windows 0a6c257 -dead_strip is now the default on Darwin fe75d2d Ensure mkUserGuidePart is compiled with current GHC version e8d7432 testsuite: Add performance testcase from #12707 12ad4d4 Throw an exception on heap overflow 226c535 base: Add Foreign.ForeignPtr.plusForeignPtr. 8a76d32 Check that type variable does not reference itself in its kind signature 58e68b3 Enable subsections via symbols on iOS 89d4d26 users-guide: Produce OpenSearch description fe8bc14 Add doc header to Dynamic's re-export of Typeable 6de7613 event manager: Don't worry if attempt to wake dead manager fails eee8199 Remove deprecated InteractiveEval API 5857dfb Remove tyConString b1923ed Fix typo in comment c2bd62e Expose purgeObj in ObjLink 35a5b60 testsuite driver: don't append to existing output files 22845ad Fix terminal corruption bug and clean up SDoc interface. 266a9dc Don't use the splitter on Darwin 09bce7a Mark *FB functions INLINE[0] (Fixes #13001) 8b15fc4 Fix references in let/app invariant note 2be364a Inline partially-applied wrappers 436aa7a Revert "event manager: Don't worry if attempt to wake dead manager fails" 5f9c6d2 Support for using only partial pieces of included signatures. 9f169bc Attach warnings to non-PVP compatible uses of signatures. 0bbcf76 Warn if you explicitly export an identifier with warning attached. e41c61f Improve Backpack support for fixities. 5def07f Revamp Backpack/hs-boot handling of type class signatures. 8744869 Rewrite module signature documentation. f59aad6 Fix handling of closed type families in Backpack. 501de26 Improve coment in typecheckIfacesForMerging. f9df77e Add mkUserGuidePart.cabal to .gitignore c6b0486 Typos in manual, comments and tests 89ce9cd Small refactoring in TcErrors f5f6d42 Fix top-level constraint handling (Trac #12921) 6b976eb Record evaluated-ness on workers and wrappers d3ad013 Typos in comments 8b6fa4f Spelling fixes in non-exported data type a62701f Simplify CPP logic as we now need v7.10 for bootstrapping dde63e0 Require python3 like everywhere else too 13a8521 Desugar static forms to makeStatic calls. f63c8ef Use latin1 code page on Windows for response files. 331f88d Fix abort and import lib search on Windows db91d17 Properly introduce CTimer to System.Posix.Types c13151e Improve access violation reporting on Windows 1f48fbc Revert "Record evaluated-ness on workers and wrappers" 9d67f04 LLVM: Tweak TBAA metadata codegen 1ff3c58 Add dump-parsed-ast flag and functionality 4bfe3d4 Add missing test files for T13082. be79289 Unbreak libGHCi by adding missing symbol. 5a9a173 Refine exprOkForSpeculation 563d64f Comments about TyBinders (only) 715be01 Typos in manual and comments [ci skip] 38f289f Fix API Annotations for unboxed sums 769e3ee testsuite/recomp001: Sleep to ensure that GHC notices file change b1726c1 Bitmap: Use foldl' instead of foldr 19cc007 testsuite: Bump allocations for T12234 e7e5f7a Some 8.2.1 release notes for my stuff d5cd505 event manager: Don't worry if attempt to wake dead manager fails e195add Unquote ‘import’ in bad import error message d360ec3 Split mkInlineUnfolding into two functions 2b61f52 Unbreak build with ghc-7.10.1 e324e31 Typos in comments only [ci skip] 70472bf Spelling fixes in comments [ci skip] 3046dbb testsuite: Really fix recomp001 0b7cd65 Clean up RTS Linker Windows. 852c6a0 Modify ForeignPtr documentation in light of plusForeignPtr 181688a Improve suggestion for misspelled flag including '=' (fixes #11789) 0d769d5 Add CBool to Foreign.C.Types 38374ca Fix get_op in the case of an unambiguous record selector (#13132) e7985ed Update levity polymorphism f5bea98 Fix the GHC 7.10 build f07a6c1 Don't error on missing Perl, just warn and disable object splitting. bf1e1f3 Add explicit foldMap implementation for Maybe 9be18ea Fix a nasty bug in exprIsExpandable b78fa75 Simplify and improve CSE b8f1b01 Test Trac #11444 5ff812c check-cpp.py: change rb'foo' to br'foo' for Python 3.2 compatibility 7026edc Add 'type family (m :: Symbol) <> (n :: Symbol)' a2a67b7 Bump Cabal submodule d49b2bb Allow top-level string literals in Core (#8472) 33140f4 Show explicit quantifiers in conflicting definitions error b476131 Add a failing test for #13099 b626a00 testsuite: Don't fail if "target has RTS linker" field is missing c43011d Clean up some shell code and M4 quoting 15b9a85 Warn on missing home modules f9ccad2 Always use -Xlinker for -rpath 560bc28 Revert "Remove unnecessary isTyVar tests in TcType" 238f31c configure.ac: Eliminate stray close bracket 3f1a21d testsuite: Bump allocations on T5321Fun and T12707 5d38fb6 Remove clean_cmd and extra_clean usage from .T files 294f95d Preserve coercion axioms when thinning. bbe8956 Rewrite Backpack comments on never-exported TyThings. 9ef237b Failing test for #13149. 6850eb6 Improve pretty-printing of IfaceCoercions 2b64e92 Apply the right substitution in ty-fam improvement 80560e6 Typos and grammar in manual/comments 18ceb14 Make checkFamInstConsistency faster 729a5e4 Don't quantify implicit type variables when quoting type signatures in TH 596dece Record evaluated-ness on workers and wrappers 532c6ad Make tickishContains faster 368d547 typecheck: Fix note 1761bfa users-guide: Document -dppr-ticks 53e2e70 Ensure that scrutinee constant folding wraps numbers abaa681 Re-sort case alternatives after scrutinee constant folding (#13170) a8c81f3 Document -fspecialise-aggressively 8f49f6d Add a failing test for #13102 7726fd7 Remove unused LOCAL_GHC_PKG definition from a test Makefile 90e83a7 Skip path_with_commas when dyn unavailable 9fd87ef Don't put foralls in front of TH-spliced GADT constructors that don't need them 99f8182 Partially revert D3001 deb75cb UniqSet: Implement unionManyUniqSets in terms of foldl' instead of foldr efc8e3b nativeGen: Use `foldl'` instead of `foldr` in free register accumulation 2cc67ad HscTypes: Use foldl' instead of foldr 2aaafc8 Bump Win32 version. 65cc762 testsuite: Bump compiler allocations of T5837 675b54f Update .mailmap e4ae78a Typos in comments [ci skip] a1cd959 Add myself [ci skip] 078c211 Update Win32 submodule to fix Windows build 1a3f1ee COMPLETE pragmas for enhanced pattern exhaustiveness checking 95dc6dc Template Haskell support for COMPLETE pragmas c344005 Generalize the type of runRW# e4ab8ba Add pragCompleteDName to templateHaskellNames 88a89b7 Nix typo and redundant where-clauses ff9355e Typos in comments [ci skip] 0d1cb15 Make type import/export API Annotation friendly 50544ee Prune unneeded Derive* language pragmas ad3d2df Don't unnecessarily qualify TH-converted instances with empty contexts 3eebd1f Generalizes the type of asProxyTypeOf (#12805) d8cb4b0 Bump nofib submodule 4e63e85 Bump hsc2hs submodule 2ffcdfa Fatal if we try to reinitialize the RTS 06b9561 Fix the right-shift operation for negative big integers (fixes #12136) 2af38b0 Remove Data.Tuple doc's claim to have tuple types 1f366b8 Add delete retry loop. [ci skip] de78ee6 Document GHC.Profiling functions [ci skip] bc42e2b Convert pprTrace in isPredTy to a WARN 34a0205 UNREG: fix "_bytes" string literal forward declaration 4441f90 UNREG: add a forward declaration for local literals f60287c Fix mismatched tick in GHC.Generics documentation d2cf5de Fix deprecation warnings from containers 2ec1c83 Fix broken tests 7363d53 Check that a default type signature aligns with the non-default signature 9169111 Add a flag to emit error messages as JSON 5593573 Fixes bug #11046 f41c27d Slighly clean up symbol loading error. 5f8e234 Print COMPLETE pragmas in --show-iface f984bf2 Simplify minusInteger in integer-gmp slightly 9af1fb2 Fix links to building guides in MAKEHELP.md e9a239c Fix minor typo in README.md 32729d3 Turn libraries/integer-gmp/gmp/tarball into a submodule c71f0c4 Fix binary instance for SrcStrictness 748b797 Use top-level instances to solve superclasses where possible b3576ed Mark reallyUnsafePtrEquality# as can_fail cb4b4fe users guide: Fix markup of COMPLETE pragma examples afc05c7 README: Mention acceptability of pull requests 44f079f FloatOut: Allow floating through breakpoint ticks 4dfc6d1 Abstract over the way eventlogs are flushed b15136a user-guide: fix links and file names (fixes #13198) 25e0cfc Export callStackDoc 99e920c Typos in note header and test f660306 Update output of failing 11223 tests 4fa439e Remove very broad ignore. [ci skip] 8d5cf8b Join points 3d65411 testsuite: Update allocations for T12234 d2b681b Fix documentation NOTE about can_fail 5cb5b7a base: Derive Enum, Bounded for VecCount, VecElem f5b275a Don't tick top-level string literals 1fcede4 Introduce GHC.TypeNats module, change KnownNat evidence to be Natural b16239a Make interface loading for COMPLETE pragmas lazy eedb3df Add support for StaticPointers in GHCi 8dd82ea Spelling fixes d8ac64e Add a testcase for #13227 b103532 Exhaustiveness check for EmptyCase (Trac #10746) 895aa6d Bump haskeline submodule 5728f4b Remove INLINE pragma on loopbreaker 6128b2f users-guide: Explain behavior of verbose-core2core + dump-inlinings bbd3c39 Ditch static flags 09b8332 Get rid of ProbOneShot c2becee Bump performance mark for T9020 afa409f Use tyCoVarsOfType for CTyEqCan in shouldSplitWD 2f5cb3d Attempt to make lazy ST thread safe 9984024 Fix comment (old file names) in includes/ 31bb85f Fix comment (old file names) in rts/ 8d60d73 Fix comment (old file names) in compiler/ 4d31880 Fix comment (old filename '.lhs') in libraries/ 283acec Make split sections by default work again 18cdef3 Fix minusNatural exception to be Underflow 157a46f Update binary submodule to 0.8.4.1 2912231 Improve wrapTicks performance with lots of redundant source notes 68cbe52 Don't panic when printing match with RecUpd context bd818a7 Fix comment (old file names) in mk/ and utils/ 8212135 New internal dynamic flag: Very aggressive inlining 54b9b06 Expose cseExpr from CSE a2f39da Add liftA2 to Applicative class fbcef83 Use proper primitives in Utils.Binary 0abe736 Don't replace type family instances with the same LHS in GHCi (#7102) adb565a Don't return empty initial uncovered set for an unsat context 26f5e60 Fix comment (old file names '.hc' ) in libraries/ 563148c Fix broken link of GHC.RTS.Flags 795bc49 Fixes for OccurAnal bugs (#13221) a9754e3 testsuite: Update expected values for T13035 and T12234 b572aad Do Worker/Wrapper for NOINLINE things 2dff54b Typos in comments [skip ci] 4aae191 Typos in comments [skip ci] a28a552 Remove unnecessary use of -DGENERICS flag 2219c8c Derive <$ 17ae5e7 Typos in comments [skip ci] a0174d2 Do not inline bottoming things f77e99b Comments only b8f58d7 Another improvement to SetLevels 078beea Docs: Fix typo in glasgow_exts.rst 5ce39f6 Add Wredundant-constraints to list of flags excluded from -Wall d5e9b7f Use better map operations in CoreMonad e90f611 Clean up findPartiallyCompletedCycles 369c534 testsuite: Bump max_bytes_used for T4029 0aa3f8d testsuite: Bump bytes allocated for T5837 8c25be8 cpeApp: Make Int accumulator strict bc376d3 Update Core formalize for Levity -> RuntimeRep 062f112 Fix push_bang_into_newtype when the pattern match has no arguments 3e07126 Fix comment of `section "Exceptions"` db3a797 Fix comment (broken link to users_guide) in $(TOP)/ 015e97a Pass -v0 to ghc-pkg to reduce noise in build ouput 512f157 Update hoopl submodule b990f65 More typos in comments [skip ci] 8e9593f Improve the simple optimiser 421308e Improve -dsuppress-coercions 3eb737e Generalize CmmUnwind and pass unwind information through NCG 733e845 CmmLayoutStack: Add unwind information on stack fixups 3328ddb Cmm: Add support for undefined unwinding statements 5279b08 CmmLayoutStack: Correctly annotate Sp adjustments with unwinding information 34e3523 Fix stop_thread unwinding information 9f3c1e6 Add some commented-out tracing in SpecConstr 3cfef76 Kill inaccessible-branch complaints in record update a94b484 Back-pedal the fix for Trac #8155 7e4e6a7 Add dump flags for the renamed and typechecked hsSyn ASTs 41c7437 users-guide: Document defaults for remaining optimization flags 082936d Fix documentation for setByteArray# afaf6d5 Bump array submodule b9bebd8 Implement addCStub in template-haskell. e8f5efb Tweaks and typos in manual, note refs, comments a6a4d0e Bump array submodule d266aac Library docs: Document the order for sort and sortOn. b92ca83 Bump bytestring submodule c22cd7c testsuite: Add testcase for #13248 a5a6c52 Guard rewritableTyVarsOfType 258c719 TH-spliced class instances are pretty-printed incorrectly post-#3384 3211fa0 Spelling in comments [ci skip] 76244ec Change rewritableTyVarsOfType to anyRewritableTyVar 283a346 Prevent Template Haskell splices from throwing a spurious TypeInType error e79ef75 Relax test TH_addCStub2 so it succeeds on travis. 639e702 Refactor DeriveAnyClass's instance context inference 594123f IcmmMachOpFoldM: clarify panic message 7fac7cd Dwarf.Types: Use DW_CFA_same_value encoding when possible 17b1e0b Mark orphan instances and rules in --show-iface output a1980ec Improve the Occurrence Analyzer’s handling of one-shot functions 26eaa7e Fix #13214 by correctly setting up dep_orphs for signatures. 1a14d38 rts/Profiling: Kill a few globals and add consts 56c9bb3 rts/Profiling: Factor out report generation 07292e9 zonkCt tries to maintain the canonical form of a Ct. 64da671 Binary: Only allocate un-interned FastStrings 7938ef2 Avoid repeated list elem checks 4e2e9b7 Fix: Default FD buffer size is not a power of 2 (#13245) 805db96 Fix: hPutBuf issues unnecessary empty write syscalls for large writes (#13246) 6b4e46a bufWrite: Save extra syscall when data fills handle buffer completely. a50082c Apply SplitSections to all C compilations d3ea38e Binary: Correct endian issue when cross-compiling e46a2e1 Bump hoopl submodule to 3.10.2.2 a4ccd33 Add index entry for signature files / Backpack. 8e9ad24 Setup more error context for Backpack operations. c81f3bc Remove obsolete Backpack manual. 2f16484 Slightly reword not-exported message. 7666a9f Disable PVP warnings temporarily. 20b5dfc Typos in notes and comments [ci skip] 2d6e91e Debug: Use local symbols for unwind points (#13278) 60c4986 Typecast covers entire expression to fix format warning. 6626242 TcUnify: Assert precondition of matchExpectedTyConApp 2484d4d Refactor renaming of operators/sections to fix DuplicateRecordFields bugs 04f67c9 Expand list of always loaded Windows shared libs 2f1017b Fix ExtraSymbols jump table on Windows. c3bbd1a Allow type defaulting for multi-param type classes with ExtendedDefaultRules da49389 Implement HasField constraint solving and modify OverloadedLabels 392cec4 Update .mailmap [skip ci] bedcb71 Check local type family instances against all imported ones f90e61a Make deSugarExpr use runTcInteractive 93e65c8 Don't warn about missing methods for instances in signatures. e28fbbb Typos [ci skip] fc9d152 Comments and tiny refactor only 6bab649 Improve checking of joins in Core Lint b8c29bc Use the correct origin in SectionL and Section R f4aa998 Better perf for haddock.base, haddock.Cabal e52a335 Comments only, about inl_inline and inl_act 8d401e5 Honour -dsuppress-uniques more thoroughly e55986a Fix a substitution bug in cseCase 0e76017 Simplify OutputableBndr ca54315 Fix a Backpack recompilation avoidance bug when signatures change. 22dba98 Fix recompilation tracking on signatures. fd2d5b6 Improvements/bugfixes to signature reexport handling. 8916884 Say 'data' explicitly in IfAbstractTyCon output. 7c057b5 Bump libraries/array submodule efeaf9e Bump nofib submodule b207b53 Generalize kind of the (->) tycon 8fa4bf9 Type-indexed Typeable 42ff5d9 Disable Typeable binding generation for unboxed sums 98e494a Improve Haddock documentation for compact. dae5003 Remove ghc-api/landmine tests 0aafe51 Typos in manual, tests and comments 2d5be63 Change -dppr-ticks to -dsuppress-ticks 8a9b57f Kill off the remaining Rec [] 3f653c1 Fix Core pretty printer 8dd4e3b Remove redundant import 27a2854 A number of Typeable wibbles from review 087dbbe Bump Cabal submodule 6ad89d7 Bump a few more performance regressions from Type-indexed Typeable 240b43e Bump Win32 submodule to 2.5.1.0 7153370 Bump time submodule to 1.8 b7265ff build.mk: Add option for debug symbols 59026b3 Spelling in comments only fd841f8 Fix DeriveAnyClass (again) 713ebd7 Fix computation of dfun_tvs in mkNewTypeEqn 95cbb55 Refactor inferConstraints not to use CPS 82694e6 testsuite: Fix allocations of T10547 e790126 Improve Core Lint, mainly for join points 6e32884 Fix SetLevels for join points 4080a63 Minor spelling, grammar, and formatting fixes 611f998 Replace some pushTcLevelM's with pushTcLevelM_ 0d43f74 A little refactoring of the simplifier around join points 0c9d9de Remove panics for TcTyCon e3e218e A bit more tc-tracing in TcTyClsDecls c750808 Disallow class instances for synonyms 3c62b1d Gather constraints locally in checkMain 499a15d Test Trac #13300 9ef2749 Fix all broken perf tests on x64 Windows 8ccbc2e Bump Cabal and containers submodules b125392 Test Trac #13271 484f8d3 Fix ApplicativeDo constraint scoping fed7136 Test Trac #13244 254bc33 A much nicer solution for typechecking ApplicativeDo c8d995d Bump time submodule c347a12 Revert recent submodule bumps 992ea02 Changelog notice for compact. 5841574 Drop NFData constraint from compact. 8a6b8c5 Export commentToAnnotation from Lexer.x 9a2a2ae Spelling only [ci skip] 050f05d testsuite: Bump a performance tests de80558 Give better error message with you run ghc foo.bkp 0a77ced Have --backpack complain if multiple files are passed. a204333 JSON profiler reports 3cb9b52 Set $1_$2_SplitSections in distdir-opts.mk not build-package.mk 48a967c testsuite: Remove old python version tests 7d116e5 rts: Correct the nursery size in the gen 1 growth computation 6ca6a36 base: Add handling of -- to getArgs for Windows bb1c660 ghci users guide: mention "~" expansion in :add 12e21d3 Use half as much memory when reading interfaces 39d926c More tracing in SpecConstr 8f8016a Include OverloadedRecordFields selectors in NameShape. 4ad3620 Fix parsing of And chains in BoolFormula 8d64395 Correct Windows libdir assumptions. c88b7c9 Add instances for (:~~:) mirroring those for (:~:) a6e13d5 Make exprIsConApp_maybe work better for literals strings 67c2e07 Add API Annotation AnnSignature for backpack signature modules 9b859ef Make SCCFunSig tag Located for ghc-exactprint 00c0120 Add a comment explaining CompleteMatchSig in HsBinds 93ffcb0 Document AMP as a Report deviation 9d17028 Record full FieldLabel in ifConFields. 7c060e4 Fix validate. 8f15ab9 Delete redundant import. 8f20844 Correctly pretty print a wild card in infix position a0b4a2a Rename compact to ghc-compact. cae1a71 Bring in unicode variants of API Annotations for HsBracket 41e54b4 Load dependent dlls. 9968502 Make list of deprecated symbols on Windows weak. be3f436 Load `pthreads` by default on Windows 97b1505 rts: Usage message wibbles d4b6dee testsuite: Bump down T2762 number 517ad20 Add testcase for #13340 ad617a3 Bring sanity to openTempFile 2aac0ba Update OverloadedLabels docs and document HasField ff9ff4a Change -ddump-tc-trace output in TcErrors, slightly 9bc4311 Fix SetLevels for makeStaticPtr a7eeb60 build system: Persist CrossCompiling in binary distributions d2f4849 Coercion: Try dropping constraintIsLifted axiom bcffc35 Move Typeable Binary instances to binary package b494689 users-guide: Add documentation for JSON profile format 0d86aa5 Add support for concurrent package db access and updates 6dfc5eb Ensure that Literals are in range ac55394 Bump hpc submodule to allow time-1.8 35b5790 Manually move extra_files for tests T9579_* 8bb63c2 Remove extra_files entries for deleted tests 98119f5 tests: manually move some extra_files into *.T files 3415bca tests: remove extra_files.py (#12223) 5c95e6b Remove outdated information about main() in HSrts (#1) 9603de6 Treat all TyCon with hole names as skolem abstract. 923d7ca Subtyping for roles in signatures. e4188b5 Refactor floating of bindings (fiBind) 4f38fa1 Add -fspec-constr-keen 76f2cd0 Occurrence-analyse the result of rule firings c0af206 Explicitly capture whether a splice has a dollar prefix 0f7a369 Stop uniques ending up in SPEC rule names 990f182 Fix windows build broken by D3080 (0d86aa5904e5a06c93632357122e57e4e118fd2a) c435402 Fix Mac OS X timestamp resolution bug. 377bf37 Clear import path in --backpack mode to not accidentally pick up source files. 36b6e13 DmdAnal: Clarify reference to Cardinality Analysis paper e94bfb6 configure: detect whether -lpthreads is necessary for pthreads 1db71f5 base: Expose Module from Type.Reflection 5dc28ba Add Eq instances for TrName, Module d0508ef When floating, don't box an expression that's okay for speculation (#13338) c662d41 Small changes to expression sizing in CoreUnfold c686af5 Add flag allowing convenient disabling of terminfo support db2a667 rts: Allow profile output path to be specified on RTS command line 29b5723 Again disable stage0 terminfo on Windows 1990bb0 Make Specialise work with casts fc6c222 Inline data constructor wrappers in phase 2 only 65c41cc config.mk.in: Disable terminfo support on iOS 23aca13 iOS: shared objects have .dylib extension. aa2143e Improve documentation for CreateBCOs Message. 3e33d33 Drop copy step from the rts/ghc.mk 122c677 Add COMPLETE pragmas for TypeRep and ErrorCall pattern synonyms 5fdb2b1 Try submodule bumps again defef52 testsuite: Bump down T5837 and T10370 allocations 55efc97 Combine identical case alternatives in CSE 2effe18 The Early Inline Patch 4f10a22 Fix redundant import in CSE cdf6b69 Add VarSet.anyDVarSet, allDVarSet 871b63e Improve pretty-printing of types 6eb52cf Improve SetLevels for join points 777b770 Mark non-recursive join lambdas as one-shot 2ab6ce7 Move isJoinId, isJoinId_maybe to Id 916658d Update containers again b86d226 rts: Fix build 701256d Change catch# demand signature cbe569a Upgrade UniqSet to a newtype d118807 Document interaction between ApplicativeDo and existentials (#13242) d4a6a7f Fix expected result from T13143 fb06bee Bump bytes allocated for T12234 537ce41 Typeable: Rename KindRep bindings to $krep... 55f6353 SymbolExtras: A bit of spring cleaning 5f7b45a Properly acquire locks on not yet existing package databases 63191e9 testsuite: Mark T13340 as fixed 27a1b12 User manual: Fix GADT paper link ae67619 Eliminate ListSetOps from imp_trust_pkgs bc332b3 Prohibit RULES changing constructors f56fc7f Extend Windows runtime loader libsearch 4aada7a More comments on role subtyping, unsoundness fix. 984c609 Disallow non-nullary constraint synonyms on class. e710686 Injective type families imply nominal injectivity, but NOT rep inj fb5cd9d Properly represent abstract classes in Class and IfaceDecl df919fb Fix roles merging to apply only to non-rep-injective types. bba004f Prevent users from defining instances for abstract classes. 57ef18a Typofix. 57d969e Fix T12234 stat mistakes a6874e5 Add -fwhole-archive-hs-libs 0b92290 Print out sub-libraries of packages more nicely. fce3d37 Don't allow orphan COMPLETE pragmas (#13349) e12ebf8 Fix up test results. 27bf6b6 Don't float out expressions that are okay for speculation 4b1f072 Add suggestion for PatternSynonyms parse error (fixes #12429) 488a9da Changed parser message for RankNTypes (#12811) 6421c6f testsuite: Move echoing commands in make invocations to VERBOSE=5 615ded1 Show: Add ShowS for ", " 0d2f733 Read COMPLETE sets from external packages ca538b8 testsuite: Fix output due to recent COMPLETE changes c02896a Revert "Read COMPLETE sets from external packages" 61e760b Update test completesig04 9808ebc testsuite: Bump down allocations for T12707 fa360ea testsuite: Add comment clarifying intention of completesig04 a694cee TcTypeable: Try to reuse KindReps c1dacb8 Produce KindReps for common kinds in GHC.Types 10d28d0 testsuite: Add test for floating-point abs (numrun015) 6446254 Deserialize IfaceId more lazily 5ed56fc Comments only, in CSE (#13340) d5e0b4b Allow iOS to load archives through the linker 0ce11ae Add test to ensure that SPEC rules are named deterministically 96f5656 testsuite: Bump down allocations of T4029 2f8534b testsuite: Add a NaN case to numrun015 a86e68c Fix a tiny typo 0fd8340 testsuite: Fix double test of +Infinity 2e58c3b Update dangling Note reference e901ed1 configure: Don't pass GHC's sanitized triple to libraries' configure 5e5f8c8 testsuite: Add expected output for T8848 31b3d0c testsuite: Bump down allocations for T4029 2e43848 Fixes a spaceleak in `maximumBy` and `minimumBy` (#10830). 35ca135 Reexport CmpNat and friends (defined in GHC.TypeNats) from GHC.TypeLits 669333d Drop HAVE_containers_050 from bootstrap flags 9304df5 Fix CSE (again) on literal strings 9b2c73e Make TH_Roles2 less fragile 1163f4f Tiny refactor 995ab74 Comments only fb9ae28 Make FloatOut/SetLevels idemoptent on bottoming functions 749740f Typos in comments and manual 29b6845 Add SplitSections = NO to build flavors with SplitObjs = NO c02d03d Add -dno-debug-output to validate GhcStage1HcOpts 8ca4bb1 Read COMPLETE sets from external packages 016b10c Add GCC bin folder to search path. 3fdabe9 Changed OverLit warnings to work with negative literals (#13257) f57bd2a add example documentation for tuple Applicative 6177c0d Disallow unboxed string literals in patterns (#13260) 1831208 base: Kill out-of-date Notes 494907f testsuite: Add test for #11076 cd9c709 Update .mailmap [skip ci] 2f115a1 A few remarks on role subtyping in the manual. 2fa4421 Add rule mapFB c (λx.x) = c 1686f30 Mangle .subsections_via_symbols away. d91b104 primops: Add comment describing type of atomicModifyMutVar# 5dddf35 testsuite: Disable linkwhole test on Windows 99fe579 Typos in changelog and comments 48759c0 Fix comment 12ccf76 Generate better fp abs for X86 and llvm with default cmm otherwise ecb880c base: kevent.filter is signed 30d69f4 ghc-pkg: Consider .conf files when computing package db mtime 6297996 DsMonad: Collect DPH things 4bd2232 Desugar: Refactor initDs bd66817 Win32: bump submodule to v2.5.2.0 8e05370 Join points can be levity-polymorphic fdb594e Comments only [ci skip] 6a94b8b Fix strictness for catchSTM a02b80f Bump haskeline submodule to fix Windows build. de62f58 base: Import Data.Int in KQueue 0fac488 Allow compilation of C/C++/ObjC/ObjC++ files with module from TH 87a2d37 testsuite: Bump allocations of T4029 9e15db4 KQueue.hsc: fix build failure on FreeBSD 9ff0574 Comments only [ci skip] 06c8ce4 Update crt to latest. 8fa1d5a get-win32-tarballs: Use haskell.org mirror 3b40450 get-win32-tarballs: Rework handling of hashing 665cefe Add a comment to the mapFB rules 7b80168 get-win32-tarballs: More reworking of tarball maintenance 7b087ae Make raiseIO# produce topRes 90009cf llvm backend: Put string constants in .rodata.str.* sections (#13265) 5dce216 configure.ac: Bump version to 8.3 712c45d integerConstantFolding: no longer broken with -DDEBUG (#1106) a6f9c44 Revert "configure.ac: Bump version to 8.3" 37a415e Fix test results for T13380 b09bf4b configure.ac: Ensure that we handle case of non-present --target 6b15dfe Data.Typeable: Export splitTyConApp, typeRepArgs, and typeRepTyCon 2b5b9dc Fix typo in base changelog a6e06c7 configure.ac: Bump version to 8.3 46246a6 implement missing Fabs{32,64} on i386 NCG and UNREG 900cfdc Do not generate a data-con wrapper for !Int# bc0f3ab Deal with JoinIds before void types 7e96526 Fix TcSimplify.decideQuantification for kind variables 48d1866 Improve error messages for skolems af6ed4a Fix constraint simplification in rules 2d3cb34 Define TcSimplify.simplifyTopImplic and use it 4eeb327 Drop redundant import 2209d5e Comments only 18d94e9 testsuite: Bump T10359 allocations 8db7949 Bump time submodule 3ca252b Fix bkpcabal03 test. 8d61a60 dsGRHSs: Remove unused pattern variables argument 7b095b9 Emit Core lint warnings on stderr, fix #13342 740ecda Observe #13267 in release notes e5453a0 Remove `runs` function which already exists in base 2f2622c KQueue: Eliminate redundant import 9297c6f Replace debugging trace with a proper WARN 2c78def Don't reference elSupremum in haddock for Lifetime Monoid ae0ccf8 Elaborate further on ZipList Applicative docs c77b767 unlit: replace the SHEBANG with an empty line 70274b4 Add `-fmax-errors` flag e61b4a4 Add COLUMN pragma 72ab738 Maybe Monoid doc: "is no semigroup" -> "used to be no semigroup" dd3b06a Broaden demand analysis IO hack notes 11ea370 Make exports from Data.Typeable and Type.Reflection consistent a3e4f69 Typeable: Fix remaining typeRepX referencds cf74b67 testsuite: Fix use of wc in T13340 40a0c00 testsuite: Fix peak_megabytes_allocated for T4029 ed28170 Bump nofib submodule 08e73cc Fix #13382: Put join ceiling underneath lambdas 50512c6 Typos in manual and comments 82b4059 Fix CaseIdentity optimisation AGAIN 1217df4 Introduce and use mkLetRec, mkLetNonRec 34f9172 testsuite: Bump allocations for T4029 b335f50 Further document :type +v's role in analyzing -XTypeApplications in GHCi 67345cc Allow associated types to pattern-match in non-class-bound variables 4b673e8 Fix Windows GCC driver e0c433c Fix #13337. d357f52 Shortcut a test in exprIsOk 5d9378e Reimplement minusList using Set 899fb88 testsuite: Bump margin of T4029 to 15% a7be163 Always build GHCi libs cc9d574 Introduce and use EnumSet in DynFlags 086b514 Introduce putLogMsg cec9070 Bump hsc2hs submodule 7e273ea Decrease locked region size on Windows to fix ERROR_LOCK_INVALID_RANGE 1cbc7c3 Bump nofib submodule ba43105 Bump hsc2hs submodule 2fd283b Bump unix submodule bc21ea0 GHC.Word: Move Read instances to GHC.Read b301f78 Save renamed syntax when signature merging. 138434f GHC_STAGE1 isn't defined, use other form. 7a38783 Typos in manual and comments [ci skip] 4dc9930 Comment coercion flattening [skip ci] dca44ad Fix #12709 by not building bad applications fa13c13 Fix #13202 by failing more eagerly in tcRnStmt 02cc8f0 Fix #13343 by not defaulting SigTvs 3cfee57 Remove solveSomeEqualities 66d174a Test #13435 in typecheck/should_run/T13435 567bc6b Improve Lint a little a7dbafe No join-point from an INLINE function with wrong arity ad19104 Revert "GHC_STAGE1 isn't defined, use other form." 763f43e OccurAnal.hs: Fix "Adjusting for lambdas" note name e0f1054 OccurAnal.hs: Add an assert for an invariant 105a5f4 Update link to paper about demand analyser in user guide d744c86 genSym: Fix DEBUG build 9c04129 users-guide: Document TemplateHaskell availability bf3952e mkUserGuidePart: Remove duplicate -XDeriveGeneric entry 713ff92 Fix Windows x86 build 09485bb UniqMap implementation. 40b65db Document the perplexing reversed nature of extraPkgConfs and friends. e0eaea9 Correctly account for -package-db ordering when picking packages. 2ac13c1 Let GHC know MutVar# ops can't fail 25b2c1b Bump unix submodule 8ef3a3c testsuite: Bump performance test allocations acd85ce Haddock submodule update. 30d68d6 Make unsafeInterleaveST less unsafe 90d9e97 Bump haddock submodule adf27d6 Allow colors to be customized 1b37440 config.mk.in: Add bzip, gzip, and xz executable names to be overridden fc41fdc ghci/Linker.hs: Fix a typo in error message 1dd60ac Typos in comments (notes too) [ci skip] 5671e22 Improve tracing in OccurAnal 8429a20 Cmm: remove a few unused type aliases caf94b0 x86 nativeGen: Fix test with mask in range [128,255] (#13425) ee7241c Document hithertoo undocumented HPCTIXFILE option. 27c9a7d testsuite: Add failing testcase for #13233 be8122a testsuite: Add testcase for #13429 6c73504 linker: fix OpenBSD build failure, EM_PPC64 is not defined there ff6ee99 testsuite: Make T10245 pass on 32-bit platforms bc9f280 Eliminate word-size dependence in HsDumpAst output 94ec48f rts: Fix stat output on 32-bit platforms aecbfb9 testsuite: Allow join007 to pass on 32-bit machines 6d774ff testsuite: Update performance numbers for 32-bit platforms a1b7e86 testsuite: Note x87 terribleness in num009 d5847cf testsuite: Add 32-bit output for compact_share test 86a0c8f Bump array submodule 2f8a3e3 Bump array submodule 43e7b23 Drop dead code in rts/{Prelude.h,package.conf.in} 14b46a5 Recompile if -fhpc is added or removed (#11798) 23da02b testsuite: Only run T13143 in optasm way 140a2d1 testsuite: Mark T12622 as broken in ghci way fdbbd63 Make mmap r+w only during preload for iOS. 8ed29b5 rts linker: Introduce MachOTypes 938392c Add ocInit_MachO f1ce276 Refactor MachO.c e8a2741 Adds aarch64 linker for mach-o files. a6ce7f3 Remove unused argument from importSuggestions d819e41 Only use locally bound variables in pattern synonym declarations a6675a9 Don't redefine typedef names 1e06d8b Simplify the logic for tc_hs_sig_type af33073 Eliminate a user manual warning 7e1c492 Typechecker comments and debug tracing only 7c7479d Fix explicitly-bidirectional pattern synonyms e0ad55f Fix error-message suppress on given equalities feca929 Fix 'unsolved constraints' in GHCi de4723f Remove utterly bogus code 5025fe2 -fspec-constr-keen docs typos [skip ci] cea7141 Fix #13458 b5c8120 Complete the fix for #13441 (pattern synonyms) eb6ccb7 Test Trac #13490 08a6fc6 Spelling in comments only [ci skip] 074d13e Fix #13433 c77551a Make the test fail if compiled without -threaded e07211f Zap Call Arity info in the simplifier 8674883 Allow unbound Refl binders in a RULE 60d338f Add a couple of HasDebugCallStack contexts f88ac37 Fix ASSERT failure in TcErrors 01e1298 cg057: accept output 5ebf83e Fix scc001 fb7e5bd testsuite: More 32-bit performance changes b04ded8 base: Check for path separators chars in openTempFile' template string 5856c56 Fixed error messages for RecursiveDo (#8501) 04ea4c3 Print module when dumping rules 154d224 Allow operators as record pattern synonym fields 81f5b6e Check TargetPlatform instead of HostPlatform for leading underscore 924a65f Various patches to support android cross compilation 26c95f4 Show valid substitutions for typed holes 01b062e unique: fix UNIQUE_BITS crosscompilation (Trac #13491) ff7094e Typos in comments [ci skip] 69f070d Deriving for phantom and empty types 03c7dd0 Disable bogus lint checks about levity polimorphic coerions 2964527 Refactor simplExpr (Type ty) 6575f4b Clean up coreView/tcView. e13419c Fix space leaks in simplifier (#13426) 546c2a1 testsuite: Update Windows allocations for T12234 3082879 askCc should be using the linker, not the compiler 71916e1 Remove Core Lint pass on occurrence analysis output (#13220) 74615f4 UNREG: ignore -fllvm (Trac #13495) a094aa7 rts: print incorrect prev_what_next 616a3b4 testsuite: Add regression test for #13474 83ac462 Don't derive showList 3b5f786 Optimise common cases of GHC.setProgramDynFlags f2b10f3 Stamp out space leaks from demand analysis 03e3425 compiler/ghc.mk: fix GhcWithInterpreter=NO build failure d89b047 FastMutInt: fix Int and Ptr sizes when crosscompiling 61ba451 Report heap overflow in the same way as stack overflow dfac365 :cd affects the iserv process too 4ed3397 testsuite: Fix GhciCurDir test d724ce3 Add a perf test for deriving null 115e7eb Update containers submodule to official 0.5.10.2 cb18447 configure.ac: fix NCG support in --target= 9110556 configure.ac: add aarch64 to list of registerised bf5e0ea Derive the definition of null d4e8ebc Minor comment updates on CSE. 5fb485a Fix recompilation avoidance bug for implementor of hsig. 5db4155 mk/boilerplate.mk defines STAGE1_GHC, not GHC_STAGE1. d2df718 Add more documentation on mergeSignatures. 71dadd7 Extra docs on exports_from_avail. 0c333c8 Extra docs on tcg_imports. 45d33f3 Better test coverage for module reexports in signatures. 852a43f Correctly handle wired in unit IDs in -instantiated-with 60307cb array: Clear up inconsistency in T9220 output 2301176 rts: Make out-of-memory errors more consistent f8ecc58 Various testsuite fixes for 32-bit Windows 597ea1c testsuite: Classify missing expected perf numbers as merely warnings f541fc6 Fix validate. 1e58efb hp2ps: install shell wrapper e815901 Bump Win32 submodule 38f9ead compact: Clarify mutability restriction e83af07 Revert "Make raiseIO# produce topRes" 5e968f9 HACKING: Update for Phabricator patch workflow 7e340c2 Enable new warning for fragile/incorrect CPP #if usage ff267f3 rts: Fix lingering #ifs 932b469 testsuite: Bump up timeout multiplier on T11195 5b7f504 testsuite: Add test for #13524 3d523fd base: Add test for #13525 37d7c15 base: Add test for #8684 09d7010 Use strict types and folds in CoreStats af941a9 Add regression test for #7944 5315223 validate: Clean GMP trees 1831aed Replace Digraph's Node type synonym with a data type 486b8db Add Alternative instance for ZipList (fix #13520). ce9b617 base: Mark unfold as deprecated 577f3da Typos in comments [ci skip] 4a1eed4 test for HAVE_CLOCK_GETTIME definedness 819c3db Revert "Enable new warning for fragile/incorrect CPP #if usage" 844704b Use non-canocalized triple as cross-compiler prefix 6ff98b9 config.mk.in: remove phase=0 hack for CrossCompilePrefix f2685df avoid $(CrossCompilerPrefix) for stage2 install 4671e3c config.mk.in: removed stray HaveLibDL assignment b5f6a93 Update .mailmap [skip ci] c600f3c Fix markup dd228b6 Add comments on DmdAnal space leak fix 48daaaf Don't report fundep wanted/wanted errors 2f9f1f8 Add a missing addDeferredBinding c90f833 Comments and eta expand only bac95f9 Yet another attempt at inferring the right quantification 2ab7f62 Comments only 65b185d Be less aggressive about fragile-context warrnings a8a7ca5 Fix name of Note f3af046 Enable lint checking of levity polymorphic coercions e61900c Add regression test for #13538 e5e07be base: Run num009 with -msse2 on i386 1d82e07 testsuite: Update expected performance numbers on 32-bit Linux 59c925e More changes to fix a space leak in the simplifier (#13426) 732b3db add $(CrossCompilePrefix) to 'runghc' and 'ghci' f0d98fc Do Note [Improving seq] always 54895c9 fix 'make install' for cross-stage2 ff84d05 cross-build 'unlit' and 'hp2ps' for stage2 install 5282bb1 Parenthesize type/data families correctly for -ddump-splices 87377f7 Add a Note [Call Arity and Join Points] b55f310 StgCse: Do not re-use trivial case scrutinees ddc0591 Add a second regression test for #13536 b1acb16 Typos in bang patterns user manual [skip ci] 42ef084 Improve `readChan` documentation: 40a2ed0 base: Fix erroneous reference to Data.Reflection in documentation 3a0e5e0 Fix form of note d463107 Enter iserv-proxy 185834e [MachO] Use OBJFORMAT_MACHO. e662a6c [Elf/arm] Thumb indicator bit only for STT_FUNC fc2a96a Typos in comments [ci skip] 751996e Kill off complications in CoreFVs b5b7d82 Improve demand analysis for join points 8346334 Fix another literal-string buglet ebb36b2 Add Outputable instance for ArityType 8d8d094 Make let and app consistent in exprIsCheapX 2d96edd Use -G1 for reliable peak mem usage bb3712b RnEnv cleanup aa20634 base: Implement bit casts between word and float types 0ecd7fa arc-linters: Add linting of #ifdef x and #if defined x 2c1312b Remove GhcDynamic (in favor of DYNAMIC_GHC_PROGRAMS) 2fc9c3e Suggest correct replacement flag name for -dppr-ticks fa5a73f Allow qualified names to be children in export lists 210b43f [linker] Remove dead code (ELF_FUNCTION_DESC) 8121748 Fix typo in ReadP (succeds -> succeeds) 68c00a1 Drop special handling of iOS e07cd50 Split up RnEnv into 4 modules, RnUnbound, RnUtils and RnFixity 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 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" 70191f5 Add a test for #11272 56de222 Add a test for #12600 1269aff includes/Stg.h: '#if sparch_HOST_ARCH' -> '#if defined(sparch_HOST_ARCH)' 2a971e3 Update unix submodule 20c39b7 ProfilerReportJson.c: fix out-of-bounds access 230416f rts: annotate switch/case with '/* fallthrough */' d5414dd rts/linker/ElfTypes.h: restore powerps (and others) support e527fc2 Stress test for nested module hierarchies 06ad87e Revert "Stress test for nested module hierarchies" ffbcfff Stress test for nested module hierarchies 8bf50d5 Revert "Use a deterministic map for imp_dep_mods" bc06655 users-guide: Document -g flag 49012eb Print warnings on parser failures (#12610). efd113f testsuite: Add testcase for T13658 2c21d74 Kill off unused IfaceType.eqIfaceType fea9a75 Tiny refactor cec7d58 Fix the pure unifier d9e9a9b Fix #13703 by correctly using munged names in ghc-pkg. d6461f9 Handle type-lets better 7b52525 Insert missing newline 433b80d Ensure that insolubles are fully rewritten c039624 Fix Haddock markup 875159c Comments and white space only d06cb96 Refactor freeNamesIfDecl 8fe37a0 Account for IfUnpackCo in freeNamesIfDecl 2501fb7 Fix scoping of data cons during kind checking 4e0e120 Modern type signature style in Module 40210c3 Improve error msg for simplifier tick exhaustion 0a754e6 Failing test case for #13734 0102e2b CNF: Silence pointer fix-up message unless gc debugging is enabled 53c78be Compile modules that are needed by template haskell, even with -fno-code. 80d5190 base: Explicitly mark Data.Either.{left,right} as INLINABLE 8646648 Correctly expand lines with multiple tabs 5b8f95d A few documentation fixes 2108460 Pretty-print strict record fields from ifaces correctly 82eab62 Bump to LLVM 4.0 6f8c3ce Fix levity polymorphism docs 5179fd4 Add missing "do" to example in arrow docs. d6686a2 Ensure package.cache is newer than registration files after make install 0440af6 Rewrite boot in Python 83ee930 fix a memory leak in osNumaMask dac49bd Handle file targets in missing home modules warning 139ef04 Add "header" to GHC_COLORS 17fef39 Testcase for #13719 2bc3a05 Testcase for type family consistency checks 033f897 Extend ModuleSet with useful functions 1fd06de aclocal.m4: allow override of dllwrap and windres when cross-compiling 432a1f1 mk/config.mk.in: lower -O2 optimization down to -O1 on UNREG 1076010 ghc.mk: rename installed ghc-stage1 on non-windows 6166b59 base: Fix a few TODOs in Typeable.Internal a29132e rts: Make compact debugging output depend upon compact debug flag 0b4b4a3 Typos in comments and manual [ci skip] 1013194 Comments only c997738 Pattern synonyms and higher rank types 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 b5c73a9 Modern type signature style in UniqSet 8bfab43 Efficient checks for stable modules 69d9081 Faster checkFamInstConsistency d39a340 aclocal.m4: add support for versioned darwin triplets 750a25f A few typos [ci skip] 35c7ea8 [iserv] move forkIO 5164cce aclocal: Fix regression in linker detection 93489cd Better import library support for Windows d0fb0df Add a flag reference entry for -XTypeInType bf775e9 Remove references to static flags in flag reference 2abe54e Make GHCi work when RebindableSyntax is enabled 811a298 GHC.Stats cleanup a786b13 Use lengthIs and friends in more places ff363bd ghc.mk: Ensure that ghc-pkg path is quoted 6597f08 Test Trac #13784 a65dfea Make the MR warning more accurage c9eb438 Desugar modules compiled with -fno-code 8e6ec0f Udate hsSyn AST to use Trees that Grow e77b9a2 Typo in output of remote slave startup [merge cand] 92a4f90 Spelling typos 2b74bd9 Stop the specialiser generating loopy code ef07010 Test Trac #13750 bca56bd Fix slash escaping in cwrapper.c 5984729 Fix a lost-wakeup bug in BLACKHOLE handling (#13751) 3e8ab7c Linker: Fix whitespace 1c76dd8 Revert "Make LLVM output robust to -dead_strip on mach-o platforms" ffd948e Bump nofib submodule 7bb2aa0 testsuite: Add performance test, Naperian 1c83fd8 [linker] fix armv7 & add aarch64 cd8f4b9 Check target libtool 3ee3822 Refactor temp files cleanup 56ef544 Add tcRnGetNameToInstancesIndex b10d3f3 Don't pass -dcore-lint to haddock in Haddock.mk b2b4160 Correct optimization flags documentation 0d94a3e linker: Fix cast-to-uint64_t 7e0ef11 Fix a bug in -foptimal-applicative-do 8f72608 users-guide: Document multi-line DEPRECATED pragmas f942f65 Improve getNameToInstancesIndex dcdc391 Fix #13807 - foreign import nondeterminism 6ddb3aa Add perf test for #12545 9a3ca8d Support signatures at the kind level in Template Haskell 2088d0b Stop forcing everything in coreBindsSize af9612b Make -w less aggressive (Trac #12056) 0058a34 Typos [ci skip] ece39c3 Fix Haddock markup 9ed7c68 Improve error messages around kind mismatches. a82cc35 Fix #11400, #11560 by documenting an infelicity. 0ab271d Test #11672 in typecheck/should_fail/T11672. 86e1984 Don't tidy vars when dumping a type 9c7ee19 Preserve CoVar uniques during pretty printing 0b9fb29 Remove old coercion pretty-printer 8aababe Fix #13819 by refactoring TypeEqOrigin.uo_thing cbf1af5 Track visibility in TypeEqOrigin From git at git.haskell.org Tue Jul 18 19:16:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 19:16:19 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Can now load up git note data into python (92e5349) Message-ID: <20170718191619.0F20F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/92e5349bfbd3ba58f55a6c830f01ce42a00ce22a/ghc >--------------------------------------------------------------- commit 92e5349bfbd3ba58f55a6c830f01ce42a00ce22a Author: Jared Weakly Date: Tue Jul 18 12:17:57 2017 -0700 Can now load up git note data into python >--------------------------------------------------------------- 92e5349bfbd3ba58f55a6c830f01ce42a00ce22a testsuite/driver/runtests.py | 6 ++++-- testsuite/driver/testutil.py | 12 +++++++++--- 2 files changed, 13 insertions(+), 5 deletions(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index 996dae1..239003c 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -337,8 +337,10 @@ else: sys.stdout.flush() summary(t, sys.stdout, config.no_print_summary) - print("Only perf tests: " + str(config.only_perf_tests) + "\n") - print("Skip perf tests: " + str(config.skip_perf_tests) + "\n") + + if config.use_git_notes: + note = subprocess.check_output(["git","notes","--ref=perf","append","-m", "\n".join(config.accumulate_metrics)]) + parse_git_notes('perf') # Should this be hardcoded? Most likely not... if config.summary_file != '': with open(config.summary_file, 'w') as file: diff --git a/testsuite/driver/testutil.py b/testsuite/driver/testutil.py index 084ef7e..6eb7aaa 100644 --- a/testsuite/driver/testutil.py +++ b/testsuite/driver/testutil.py @@ -47,9 +47,15 @@ def lndir(srcdir, dstdir): os.mkdir(dst) lndir(src, dst) -# def git_append(note): -# def print_metrics(): -# print(config.accumulate_metrics) +# This function allows one to read in git notes from the commandline +# and then breaks it into a list of dictionaries that can be parsed +# later on in the testing functions. +def parse_git_notes(namespace): + logFields = ['TEST_ENV','TEST','WAY','METRIC','VALUE'] + log = subprocess.check_output(['git', 'notes', '--ref=' + namespace, 'show']).decode('utf-8') + log = log.strip('\n').split('\n') + log = [entry.strip('\t').split('\t') for entry in log] + log = [dict(zip(logFields, row)) for row in log] # On Windows, os.symlink is not defined with Python 2.7, but is in Python 3 # when using msys2, as GHC does. Unfortunately, only Administrative users have From git at git.haskell.org Tue Jul 18 20:39:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 20:39:32 +0000 (UTC) Subject: [commit: packages/mtl] tag 'v2.2.1' created Message-ID: <20170718203932.E52673A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/mtl New tag : v2.2.1 Referencing: 324b881b0c6dff87da0f66b36b8bcef446e238e6 From git at git.haskell.org Tue Jul 18 21:19:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 21:19:50 +0000 (UTC) Subject: [commit: ghc] branch 'wip/cabal-parsec' created Message-ID: <20170718211950.307B63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/cabal-parsec Referencing: fdae040f8121f3b27af911acff82dd2a54bd7bed From git at git.haskell.org Tue Jul 18 21:19:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 21:19:53 +0000 (UTC) Subject: [commit: ghc] wip/cabal-parsec: Enable cabal's parsec mode by adding mtl/text/parsec (fdae040) Message-ID: <20170718211953.07F183A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cabal-parsec Link : http://ghc.haskell.org/trac/ghc/changeset/fdae040f8121f3b27af911acff82dd2a54bd7bed/ghc >--------------------------------------------------------------- commit fdae040f8121f3b27af911acff82dd2a54bd7bed Author: Herbert Valerio Riedel Date: Tue Jul 18 23:08:55 2017 +0200 Enable cabal's parsec mode by adding mtl/text/parsec >--------------------------------------------------------------- fdae040f8121f3b27af911acff82dd2a54bd7bed .gitmodules | 12 ++++++++++++ ghc.mk | 11 +++++++++-- libraries/mtl | 1 + libraries/parsec | 1 + libraries/text | 1 + packages | 3 +++ rules/sdist-ghc-file.mk | 31 +++++++++++++++++++++++++++++++ utils/ghc-cabal/ghc.mk | 27 +++++++++++++++++++++++---- 8 files changed, 81 insertions(+), 6 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 fdae040f8121f3b27af911acff82dd2a54bd7bed From git at git.haskell.org Tue Jul 18 21:58:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 21:58:26 +0000 (UTC) Subject: [commit: ghc] branch 'wip/cabal_parsec' created Message-ID: <20170718215826.316093A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/cabal_parsec Referencing: 0d11176c20feb3e8627e6297735b1b952613896a From git at git.haskell.org Tue Jul 18 21:58:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 21:58:29 +0000 (UTC) Subject: [commit: ghc] wip/cabal_parsec: Enable building Cabal with parsec (0d11176) Message-ID: <20170718215829.007E83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cabal_parsec Link : http://ghc.haskell.org/trac/ghc/changeset/0d11176c20feb3e8627e6297735b1b952613896a/ghc >--------------------------------------------------------------- commit 0d11176c20feb3e8627e6297735b1b952613896a Author: Herbert Valerio Riedel Date: Tue Jul 18 23:08:55 2017 +0200 Enable building Cabal with parsec Cabal's parser has been rewritten in terms of Parsec (which is not enabled yet in Cabal-2.0 by default, but can be enabled by a cabal flag). The plan for Cabal is to drop support for the non-parsec parser, so we need to prepare GHC to cope with new situation. However, this means that lib:Cabal requires three new library dependencies: - parsec - text - mtl What complicates matters is that we need to build `ghc-cabal` early on during the bootstrap phase which currently needs to invoke `ghc --make` directly. So these additional dependencies need to be integrated into the monolithic `ghc --make` invocation which produces the `ghc-cabal` executable. >--------------------------------------------------------------- 0d11176c20feb3e8627e6297735b1b952613896a .gitmodules | 12 ++++++++++++ ghc.mk | 11 +++++++++-- libraries/mtl | 1 + libraries/parsec | 1 + libraries/text | 1 + mk/warnings.mk | 5 +++++ packages | 3 +++ rules/sdist-ghc-file.mk | 31 +++++++++++++++++++++++++++++++ utils/ghc-cabal/ghc.mk | 25 ++++++++++++++++++++++--- 9 files changed, 85 insertions(+), 5 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 0d11176c20feb3e8627e6297735b1b952613896a From git at git.haskell.org Tue Jul 18 21:58:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 21:58:42 +0000 (UTC) Subject: [commit: ghc] branch 'wip/cabal_parsec' deleted Message-ID: <20170718215842.EAD353A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/cabal_parsec From git at git.haskell.org Tue Jul 18 21:59:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Jul 2017 21:59:03 +0000 (UTC) Subject: [commit: ghc] wip/cabal-parsec: Enable building Cabal with parsec (0d11176) Message-ID: <20170718215903.91C423A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cabal-parsec Link : http://ghc.haskell.org/trac/ghc/changeset/0d11176c20feb3e8627e6297735b1b952613896a/ghc >--------------------------------------------------------------- commit 0d11176c20feb3e8627e6297735b1b952613896a Author: Herbert Valerio Riedel Date: Tue Jul 18 23:08:55 2017 +0200 Enable building Cabal with parsec Cabal's parser has been rewritten in terms of Parsec (which is not enabled yet in Cabal-2.0 by default, but can be enabled by a cabal flag). The plan for Cabal is to drop support for the non-parsec parser, so we need to prepare GHC to cope with new situation. However, this means that lib:Cabal requires three new library dependencies: - parsec - text - mtl What complicates matters is that we need to build `ghc-cabal` early on during the bootstrap phase which currently needs to invoke `ghc --make` directly. So these additional dependencies need to be integrated into the monolithic `ghc --make` invocation which produces the `ghc-cabal` executable. >--------------------------------------------------------------- 0d11176c20feb3e8627e6297735b1b952613896a .gitmodules | 12 ++++++++++++ ghc.mk | 11 +++++++++-- libraries/mtl | 1 + libraries/parsec | 1 + libraries/text | 1 + mk/warnings.mk | 5 +++++ packages | 3 +++ rules/sdist-ghc-file.mk | 31 +++++++++++++++++++++++++++++++ utils/ghc-cabal/ghc.mk | 25 ++++++++++++++++++++++--- 9 files changed, 85 insertions(+), 5 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 0d11176c20feb3e8627e6297735b1b952613896a From git at git.haskell.org Wed Jul 19 00:24:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 00:24:41 +0000 (UTC) Subject: [commit: ghc] master: Typeable: Always use UTF-8 string unpacking primitive (6ab3c5f) Message-ID: <20170719002441.02DF43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6ab3c5fdd7d292deb65a3174eb298aa4b2348e32/ghc >--------------------------------------------------------------- commit 6ab3c5fdd7d292deb65a3174eb298aa4b2348e32 Author: Ben Gamari Date: Tue Jul 18 17:50:07 2017 -0400 Typeable: Always use UTF-8 string unpacking primitive Reviewers: austin, hvr Subscribers: Phyx, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3734 >--------------------------------------------------------------- 6ab3c5fdd7d292deb65a3174eb298aa4b2348e32 libraries/base/Data/Typeable/Internal.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index cf645ad..cf3ea07 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -117,7 +117,7 @@ tyConName :: TyCon -> String tyConName (TyCon _ _ _ n _ _) = trNameString n trNameString :: TrName -> String -trNameString (TrNameS s) = unpackCString# s +trNameString (TrNameS s) = unpackCStringUtf8# s trNameString (TrNameD s) = s tyConFingerprint :: TyCon -> Fingerprint @@ -361,7 +361,7 @@ instantiateKindRep vars = go = SomeTypeRep $ Fun (unsafeCoerceRep $ go a) (unsafeCoerceRep $ go b) go (KindRepTYPE r) = unkindedTypeRep $ tYPE `kApp` runtimeRepTypeRep r go (KindRepTypeLitS sort s) - = mkTypeLitFromString sort (unpackCString# s) + = mkTypeLitFromString sort (unpackCStringUtf8# s) go (KindRepTypeLitD sort s) = mkTypeLitFromString sort s @@ -569,7 +569,7 @@ pattern KindRepTypeLit sort t <- (getKindRepTypeLit -> Just (sort, t)) KindRepTYPE, KindRepTypeLit #-} getKindRepTypeLit :: KindRep -> Maybe (TypeLitSort, String) -getKindRepTypeLit (KindRepTypeLitS sort t) = Just (sort, unpackCString# t) +getKindRepTypeLit (KindRepTypeLitS sort t) = Just (sort, unpackCStringUtf8# t) getKindRepTypeLit (KindRepTypeLitD sort t) = Just (sort, t) getKindRepTypeLit _ = Nothing @@ -586,9 +586,9 @@ mkTyCon# pkg modl name n_kinds kind_rep where mod = Module (TrNameS pkg) (TrNameS modl) fingerprint :: Fingerprint - fingerprint = mkTyConFingerprint (unpackCString# pkg) - (unpackCString# modl) - (unpackCString# name) + fingerprint = mkTyConFingerprint (unpackCStringUtf8# pkg) + (unpackCStringUtf8# modl) + (unpackCStringUtf8# name) -- it is extremely important that this fingerprint computation -- remains in sync with that in TcTypeable to ensure that type From git at git.haskell.org Wed Jul 19 00:29:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 00:29:24 +0000 (UTC) Subject: [commit: ghc] master: configure: Cleanup ARM COPY bug test artifacts (d7b1751) Message-ID: <20170719002924.0D9AC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d7b17517e26007f537feab490509c0e13e0e239a/ghc >--------------------------------------------------------------- commit d7b17517e26007f537feab490509c0e13e0e239a Author: Ben Gamari Date: Fri Jul 7 23:16:47 2017 -0400 configure: Cleanup ARM COPY bug test artifacts >--------------------------------------------------------------- d7b17517e26007f537feab490509c0e13e0e239a aclocal.m4 | 2 ++ 1 file changed, 2 insertions(+) diff --git a/aclocal.m4 b/aclocal.m4 index 71a874f..a9788bf 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2060,6 +2060,8 @@ EOF else AC_MSG_RESULT([unaffected]) fi + + rm -f aclib.s aclib.o aclib.so actest.s actest.o actest ;; *) ;; From git at git.haskell.org Wed Jul 19 12:03:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 12:03:38 +0000 (UTC) Subject: [commit: ghc] wip/rae: Improve error messages around kind mismatches. (c17d73c) Message-ID: <20170719120338.3AFE53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/c17d73c09a7577fc5ac308cf55b9ad2b06c2fcdd/ghc >--------------------------------------------------------------- commit c17d73c09a7577fc5ac308cf55b9ad2b06c2fcdd Author: Richard Eisenberg Date: Thu Jun 1 17:27:14 2017 -0400 Improve error messages around kind mismatches. Previously, when canonicalizing (or unifying, in uType) a heterogeneous equality, we emitted a kind equality and used the resulting coercion to cast one side of the heterogeneous equality. While sound, this led to terrible error messages. (See the bugs listed below.) The problem is that using the coercion built from the emitted kind equality is a bit like a wanted rewriting a wanted. The solution is to keep heterogeneous equalities as irreducible. See Note [Equalities with incompatible kinds] in TcCanonical. This commit also removes a highly suspicious switch to FM_SubstOnly when flattening in the kinds of a type variable. I have no idea why this was there, other than as a holdover from pre-TypeInType. I've not left a Note because there is simply no reason I can conceive of that the FM_SubstOnly should be there. One challenge with this patch is that the emitted derived equalities might get emitted several times: when a heterogeneous equality is in an implication and then gets floated out from the implication, the Derived is present both in and out of the implication. This causes a duplicate error message. (Test case: typecheck/should_fail/T7368) Solution: track the provenance of Derived constraints and refuse to float out a constraint that has an insoluble Derived. Lastly, this labels one test (dependent/should_fail/RAE_T32a) as expect_broken, because the problem is really #12919. The different handling of constraints in this patch exposes the error. This fixes bugs #11198, #12373, #13530, and #13610. test cases: typecheck/should_fail/{T8262,T8603,tcail122,T12373,T13530,T13610} >--------------------------------------------------------------- c17d73c09a7577fc5ac308cf55b9ad2b06c2fcdd compiler/typecheck/TcCanonical.hs | 296 ++++++++++++--------- compiler/typecheck/TcErrors.hs | 75 ++++-- compiler/typecheck/TcEvidence.hs | 8 +- compiler/typecheck/TcFlatten.hs | 31 ++- compiler/typecheck/TcRnMonad.hs | 16 +- compiler/typecheck/TcRnTypes.hs | 38 ++- compiler/typecheck/TcSimplify.hs | 32 ++- compiler/typecheck/TcType.hs | 10 +- compiler/typecheck/TcUnify.hs | 28 +- compiler/types/Type.hs | 4 +- testsuite/tests/dependent/should_fail/T11471.hs | 2 +- .../tests/dependent/should_fail/T11471.stderr | 11 +- testsuite/tests/dependent/should_fail/all.T | 2 +- testsuite/tests/gadt/gadt7.stderr | 6 +- .../tests/ghci.debugger/scripts/break012.stdout | 14 +- .../indexed-types/should_fail/ExtraTcsUntch.stderr | 6 +- .../tests/indexed-types/should_fail/T5934.stderr | 13 - testsuite/tests/polykinds/T12593.stderr | 56 ++++ testsuite/tests/polykinds/T13555.stderr | 21 +- testsuite/tests/polykinds/T7438.stderr | 6 +- testsuite/tests/polykinds/T8566.stderr | 2 +- testsuite/tests/polykinds/T9017.stderr | 10 +- testsuite/tests/typecheck/should_fail/T12373.hs | 10 + .../tests/typecheck/should_fail/T12373.stderr | 8 + testsuite/tests/typecheck/should_fail/T13530.hs | 11 + .../tests/typecheck/should_fail/T13530.stderr | 7 + testsuite/tests/typecheck/should_fail/T13610.hs | 11 + .../tests/typecheck/should_fail/T13610.stderr | 14 + testsuite/tests/typecheck/should_fail/T5691.stderr | 10 +- testsuite/tests/typecheck/should_fail/T7368.stderr | 6 +- .../tests/typecheck/should_fail/T7368a.stderr | 2 +- testsuite/tests/typecheck/should_fail/T7453.stderr | 56 ++-- testsuite/tests/typecheck/should_fail/T7696.stderr | 4 +- testsuite/tests/typecheck/should_fail/T8262.stderr | 6 +- testsuite/tests/typecheck/should_fail/T8603.hs | 4 + testsuite/tests/typecheck/should_fail/T8603.stderr | 13 +- testsuite/tests/typecheck/should_fail/all.T | 3 + .../tests/typecheck/should_fail/tcfail090.stderr | 4 +- .../tests/typecheck/should_fail/tcfail122.stderr | 8 +- .../tests/typecheck/should_fail/tcfail123.stderr | 13 +- .../tests/typecheck/should_fail/tcfail200.stderr | 6 +- 41 files changed, 555 insertions(+), 328 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 c17d73c09a7577fc5ac308cf55b9ad2b06c2fcdd From git at git.haskell.org Wed Jul 19 12:03:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 12:03:40 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #11400, #11560 by documenting an infelicity. (4e96906) Message-ID: <20170719120340.EF97A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/4e96906a585bdebef9819b9f92797614ceae78a2/ghc >--------------------------------------------------------------- commit 4e96906a585bdebef9819b9f92797614ceae78a2 Author: Richard Eisenberg Date: Thu Jun 1 18:09:05 2017 -0400 Fix #11400, #11560 by documenting an infelicity. Really, the fix for both of these is #11307. >--------------------------------------------------------------- 4e96906a585bdebef9819b9f92797614ceae78a2 docs/users_guide/glasgow_exts.rst | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index c3a2d69..6d53d25 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -8342,9 +8342,9 @@ enabled). The only way ``*`` is unordinary is in its parsing. In order to be backward compatible, ``*`` is parsed as if it were an alphanumeric idenfifier; note that we do not write ``Int :: (*)`` but just plain ``Int :: *``. Due to the -bizarreness with which ``*`` is parsed-and the fact that it is the only such -operator in GHC-there are some corner cases that are -not handled. We are aware of two: +bizarreness with which ``*`` is parsed--and the fact that it is the only such +operator in GHC--there are some corner cases that are +not handled. We are aware of three: - In a Haskell-98-style data constructor, you must put parentheses around ``*``, like this: :: @@ -8358,6 +8358,10 @@ not handled. We are aware of two: Note that the keyword ``type`` there is just to disambiguate the import from a term-level ``(*)``. (:ref:`explicit-namespaces`) +- In an instance declaration head (the part after the word ``instance``), you + must parenthesize ``*``. This applies to all manners of instances, including + the left-hand sides of individual equations of a closed type family. + The ``Data.Kind`` module also exports ``Type`` as a synonym for ``*``. Now that type synonyms work in kinds, it is conceivable that we will deprecate ``*`` when there is a good migration story for everyone to use ``Type``. From git at git.haskell.org Wed Jul 19 12:03:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 12:03:47 +0000 (UTC) Subject: [commit: ghc] wip/rae: Don't tidy vars when dumping a type (77c8e72) Message-ID: <20170719120347.4B0AD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/77c8e72c32e762f9b55887c3c966358214a403c7/ghc >--------------------------------------------------------------- commit 77c8e72c32e762f9b55887c3c966358214a403c7 Author: Richard Eisenberg Date: Fri Apr 7 11:13:32 2017 -0400 Don't tidy vars when dumping a type This makes variables print more consistenty in, say, -ddump-tc-trace. >--------------------------------------------------------------- 77c8e72c32e762f9b55887c3c966358214a403c7 compiler/types/TyCoRep.hs | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index 5ac63e5..90c6a31 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -137,8 +137,8 @@ import {-# SOURCE #-} DataCon( dataConFullSig , dataConUnivTyVarBinders, dataConExTyVarBinders , DataCon, filterEqSpec ) import {-# SOURCE #-} Type( isPredTy, isCoercionTy, mkAppTy, mkCastTy - , tyCoVarsOfTypesWellScoped , tyCoVarsOfTypeWellScoped + , tyCoVarsOfTypesWellScoped , coreView, typeKind ) -- Transitively pulls in a LOT of stuff, better to break the loop @@ -2435,7 +2435,7 @@ pprType = pprPrecType TopPrec pprParendType = pprPrecType TyConPrec pprPrecType :: TyPrec -> Type -> SDoc -pprPrecType prec ty = pprPrecIfaceType prec (tidyToIfaceType ty) +pprPrecType prec ty = getPprStyle $ \sty -> pprPrecIfaceType prec (tidyToIfaceTypeSty ty sty) pprTyLit :: TyLit -> SDoc pprTyLit = pprIfaceTyLit . toIfaceTyLit @@ -2444,6 +2444,12 @@ pprKind, pprParendKind :: Kind -> SDoc pprKind = pprType pprParendKind = pprParendType +tidyToIfaceTypeSty :: Type -> PprStyle -> IfaceType +tidyToIfaceTypeSty ty sty + | userStyle sty = tidyToIfaceType ty + | otherwise = toIfaceTypeX (tyCoVarsOfType ty) ty + -- in latter case, don't tidy, as we'll be printing uniques. + tidyToIfaceType :: Type -> IfaceType -- It's vital to tidy before converting to an IfaceType -- or nested binders will become indistinguishable! From git at git.haskell.org Wed Jul 19 12:03:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 12:03:50 +0000 (UTC) Subject: [commit: ghc] wip/rae: Remove old coercion pretty-printer (dfd2d39) Message-ID: <20170719120350.0F4BF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/dfd2d3939ffda5d52fe2a7c3461045f239290491/ghc >--------------------------------------------------------------- commit dfd2d3939ffda5d52fe2a7c3461045f239290491 Author: Richard Eisenberg Date: Tue Jun 6 11:01:14 2017 -0400 Remove old coercion pretty-printer Now, all coercions are printed from IfaceType, just like types. This also changes the rendering of TransCo to use ; instead of a prefix operator. >--------------------------------------------------------------- dfd2d3939ffda5d52fe2a7c3461045f239290491 compiler/iface/IfaceType.hs | 3 +- compiler/iface/ToIface.hs | 4 +- compiler/iface/ToIface.hs-boot | 2 +- compiler/types/Coercion.hs | 107 +++++----------------------------------- compiler/types/Coercion.hs-boot | 3 -- compiler/types/TyCoRep.hs | 35 ++++++++++--- compiler/types/Type.hs | 2 +- compiler/types/Type.hs-boot | 7 +-- 8 files changed, 49 insertions(+), 114 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 dfd2d3939ffda5d52fe2a7c3461045f239290491 From git at git.haskell.org Wed Jul 19 12:03:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 12:03:44 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #11672 in typecheck/should_fail/T11672. (4a6a690) Message-ID: <20170719120344.93D2F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/4a6a690cc349453d43630a5bb8224c950f574875/ghc >--------------------------------------------------------------- commit 4a6a690cc349453d43630a5bb8224c950f574875 Author: Richard Eisenberg Date: Thu Jun 1 18:28:57 2017 -0400 Test #11672 in typecheck/should_fail/T11672. I believe this was fixed with the fix for #11198. >--------------------------------------------------------------- 4a6a690cc349453d43630a5bb8224c950f574875 testsuite/tests/typecheck/should_fail/T11672.hs | 9 +++++++++ testsuite/tests/typecheck/should_fail/T11672.stderr | 21 +++++++++++++++++++++ testsuite/tests/typecheck/should_fail/all.T | 2 ++ 3 files changed, 32 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T11672.hs b/testsuite/tests/typecheck/should_fail/T11672.hs new file mode 100644 index 0000000..8c5e2fb --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T11672.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE KindSignatures #-} +module BadError where + +import GHC.TypeLits +import Data.Proxy + +f :: Proxy (a :: Symbol) -> Int +f _ = f (Proxy :: Proxy (Int -> Bool)) diff --git a/testsuite/tests/typecheck/should_fail/T11672.stderr b/testsuite/tests/typecheck/should_fail/T11672.stderr new file mode 100644 index 0000000..d08acba --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T11672.stderr @@ -0,0 +1,21 @@ + +T11672.hs:9:10: error: + • Couldn't match kind ‘Symbol’ with ‘*’ + When matching types + a0 :: Symbol + Int -> Bool :: * + Expected type: Proxy a0 + Actual type: Proxy (Int -> Bool) + • In the first argument of ‘f’, namely + ‘(Proxy :: Proxy (Int -> Bool))’ + In the expression: f (Proxy :: Proxy (Int -> Bool)) + In an equation for ‘f’: f _ = f (Proxy :: Proxy (Int -> Bool)) + +T11672.hs:9:10: error: + • Couldn't match type ‘*’ with ‘Symbol’ + Expected type: Proxy a0 + Actual type: Proxy (Int -> Bool) + • In the first argument of ‘f’, namely + ‘(Proxy :: Proxy (Int -> Bool))’ + In the expression: f (Proxy :: Proxy (Int -> Bool)) + In an equation for ‘f’: f _ = f (Proxy :: Proxy (Int -> Bool)) diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index cc2e4e3..83ed20a 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -448,3 +448,5 @@ test('T13821B', expect_broken(13821), backpack_typecheck_fail, ['']) test('T13530', normal, compile_fail, ['']) test('T12373', normal, compile_fail, ['']) test('T13610', normal, compile_fail, ['']) +test('T11672', normal, compile_fail, ['']) + From git at git.haskell.org Wed Jul 19 12:03:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 12:03:52 +0000 (UTC) Subject: [commit: ghc] wip/rae: Preserve CoVar uniques during pretty printing (4e45b23) Message-ID: <20170719120352.CB6AE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/4e45b23bcd2582a5165240cd0f33aad4cc1d9633/ghc >--------------------------------------------------------------- commit 4e45b23bcd2582a5165240cd0f33aad4cc1d9633 Author: Richard Eisenberg Date: Tue Jun 6 10:07:16 2017 -0400 Preserve CoVar uniques during pretty printing Previously, we did this for Types, but not for Coercions. >--------------------------------------------------------------- 4e45b23bcd2582a5165240cd0f33aad4cc1d9633 compiler/backpack/RnModIface.hs | 1 + compiler/iface/IfaceSyn.hs | 1 + compiler/iface/IfaceType.hs | 9 ++++++++- compiler/iface/TcIface.hs | 1 + compiler/iface/ToIface.hs | 8 +++++--- testsuite/tests/roles/should_compile/Roles13.stderr | 2 +- 6 files changed, 17 insertions(+), 5 deletions(-) diff --git a/compiler/backpack/RnModIface.hs b/compiler/backpack/RnModIface.hs index 2e738c1..e3da067 100644 --- a/compiler/backpack/RnModIface.hs +++ b/compiler/backpack/RnModIface.hs @@ -646,6 +646,7 @@ rnIfaceCo (IfaceAppCo co1 co2) = IfaceAppCo <$> rnIfaceCo co1 <*> rnIfaceCo co2 rnIfaceCo (IfaceForAllCo bndr co1 co2) = IfaceForAllCo <$> rnIfaceTvBndr bndr <*> rnIfaceCo co1 <*> rnIfaceCo co2 +rnIfaceCo (IfaceFreeCoVar c) = pure (IfaceFreeCoVar c) rnIfaceCo (IfaceCoVarCo lcl) = IfaceCoVarCo <$> pure lcl rnIfaceCo (IfaceAxiomInstCo n i cs) = IfaceAxiomInstCo <$> rnIfaceGlobal n <*> pure i <*> mapM rnIfaceCo cs diff --git a/compiler/iface/IfaceSyn.hs b/compiler/iface/IfaceSyn.hs index 60206ea..3360d74 100644 --- a/compiler/iface/IfaceSyn.hs +++ b/compiler/iface/IfaceSyn.hs @@ -1424,6 +1424,7 @@ freeNamesIfCoercion (IfaceAppCo c1 c2) = freeNamesIfCoercion c1 &&& freeNamesIfCoercion c2 freeNamesIfCoercion (IfaceForAllCo _ kind_co co) = freeNamesIfCoercion kind_co &&& freeNamesIfCoercion co +freeNamesIfCoercion (IfaceFreeCoVar _) = emptyNameSet freeNamesIfCoercion (IfaceCoVarCo _) = emptyNameSet freeNamesIfCoercion (IfaceAxiomInstCo ax _ cos) diff --git a/compiler/iface/IfaceType.hs b/compiler/iface/IfaceType.hs index 39e3028..4ab40d4 100644 --- a/compiler/iface/IfaceType.hs +++ b/compiler/iface/IfaceType.hs @@ -109,7 +109,7 @@ data IfaceOneShot -- See Note [Preserve OneShotInfo] in CoreTicy type IfaceKind = IfaceType data IfaceType -- A kind of universal type, used for types and kinds - = IfaceFreeTyVar TyVar -- See Note [Free tyvars in IfaceType] + = IfaceFreeTyVar TyVar -- See Note [Free tyvars in IfaceType] | IfaceTyVar IfLclName -- Type/coercion variable only, not tycon | IfaceLitTy IfaceTyLit | IfaceAppTy IfaceType IfaceType @@ -204,6 +204,7 @@ Note that: to deserialise one. IfaceFreeTyVar is used only in the "convert to IfaceType and then pretty-print" pipeline. +We do the same for covars, naturally. Note [Equality predicates in IfaceType] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -242,6 +243,7 @@ data IfaceCoercion | IfaceTyConAppCo Role IfaceTyCon [IfaceCoercion] | IfaceAppCo IfaceCoercion IfaceCoercion | IfaceForAllCo IfaceTvBndr IfaceCoercion IfaceCoercion + | IfaceFreeCoVar CoVar -- See Note [Free tyvars in IfaceType] | IfaceCoVarCo IfLclName | IfaceAxiomInstCo IfExtName BranchIndex [IfaceCoercion] | IfaceUnivCo IfaceUnivCoProv Role IfaceType IfaceType @@ -395,6 +397,7 @@ substIfaceType env ty go_co (IfaceTyConAppCo r tc cos) = IfaceTyConAppCo r tc (go_cos cos) go_co (IfaceAppCo c1 c2) = IfaceAppCo (go_co c1) (go_co c2) go_co (IfaceForAllCo {}) = pprPanic "substIfaceCoercion" (ppr ty) + go_co (IfaceFreeCoVar cv) = IfaceFreeCoVar cv go_co (IfaceCoVarCo cv) = IfaceCoVarCo cv go_co (IfaceAxiomInstCo a i cos) = IfaceAxiomInstCo a i (go_cos cos) go_co (IfaceUnivCo prov r t1 t2) = IfaceUnivCo (go_prov prov) r (go t1) (go t2) @@ -1039,6 +1042,8 @@ ppr_co ctxt_prec co@(IfaceForAllCo {}) = let (tvs, co'') = split_co co' in ((name,kind_co):tvs,co'') split_co co' = ([], co') +-- Why these two? See Note [TcTyVars in IfaceType] +ppr_co _ (IfaceFreeCoVar covar) = ppr covar ppr_co _ (IfaceCoVarCo covar) = ppr covar ppr_co ctxt_prec (IfaceUnivCo IfaceUnsafeCoerceProv r ty1 ty2) @@ -1321,6 +1326,8 @@ instance Binary IfaceCoercion where put_ bh a put_ bh b put_ bh c + put_ _ (IfaceFreeCoVar cv) + = pprPanic "Can't serialise IfaceFreeCoVar" (ppr cv) put_ bh (IfaceCoVarCo a) = do putByte bh 6 put_ bh a diff --git a/compiler/iface/TcIface.hs b/compiler/iface/TcIface.hs index 3a6a407..f677935 100644 --- a/compiler/iface/TcIface.hs +++ b/compiler/iface/TcIface.hs @@ -1314,6 +1314,7 @@ tcIfaceCo = go go (IfaceForAllCo tv k c) = do { k' <- go k ; bindIfaceTyVar tv $ \ tv' -> ForAllCo tv' k' <$> go c } + go (IfaceFreeCoVar c) = pprPanic "tcIfaceCo:IfaceFreeCoVar" (ppr c) go (IfaceCoVarCo n) = CoVarCo <$> go_var n go (IfaceAxiomInstCo n i cs) = AxiomInstCo <$> tcIfaceCoAxiom n <*> pure i <*> mapM go cs go (IfaceUnivCo p r t1 t2) = UnivCo <$> tcIfaceUnivCoProv p <*> pure r diff --git a/compiler/iface/ToIface.hs b/compiler/iface/ToIface.hs index 6f2acba..d4a2115 100644 --- a/compiler/iface/ToIface.hs +++ b/compiler/iface/ToIface.hs @@ -217,7 +217,10 @@ toIfaceCoercionX fr co = go co where go (Refl r ty) = IfaceReflCo r (toIfaceType ty) - go (CoVarCo cv) = IfaceCoVarCo (toIfaceCoVar cv) + go (CoVarCo cv) + -- See [TcTyVars in IfaceType] in IfaceType + | cv `elemVarSet` fr = IfaceFreeCoVar cv + | otherwise = IfaceCoVarCo (toIfaceCoVar cv) go (AppCo co1 co2) = IfaceAppCo (go co1) (go co2) go (SymCo co) = IfaceSymCo (go co) go (TransCo co1 co2) = IfaceTransCo (go co1) (go co2) @@ -236,8 +239,7 @@ toIfaceCoercionX fr co | tc `hasKey` funTyConKey , [_,_,_,_] <- cos = pprPanic "toIfaceCoercion" (ppr co) | otherwise = IfaceTyConAppCo r (toIfaceTyCon tc) (map go cos) - go (FunCo r co1 co2) = IfaceFunCo r (toIfaceCoercion co1) - (toIfaceCoercion co2) + go (FunCo r co1 co2) = IfaceFunCo r (go co1) (go co2) go (ForAllCo tv k co) = IfaceForAllCo (toIfaceTvBndr tv) (toIfaceCoercionX fr' k) diff --git a/testsuite/tests/roles/should_compile/Roles13.stderr b/testsuite/tests/roles/should_compile/Roles13.stderr index f4b44a2..414ef80 100644 --- a/testsuite/tests/roles/should_compile/Roles13.stderr +++ b/testsuite/tests/roles/should_compile/Roles13.stderr @@ -13,7 +13,7 @@ convert :: Wrap Age -> Int [GblId, Arity=1, Caf=NoCafRefs] convert = convert1 - `cast` (_R -> Roles13.N:Wrap[0] Roles13.N:Age[0] + `cast` (_R ->_R Roles13.N:Wrap[0] (Roles13.N:Age[0]) :: (Wrap Age -> Wrap Age :: *) ~R# (Wrap Age -> Int :: *)) -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} From git at git.haskell.org Wed Jul 19 12:03:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 12:03:56 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #13819 by refactoring TypeEqOrigin.uo_thing (ea32578) Message-ID: <20170719120356.B93383A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/ea325787959da884a23f45f405bf9e3ee6329f59/ghc >--------------------------------------------------------------- commit ea325787959da884a23f45f405bf9e3ee6329f59 Author: Richard Eisenberg Date: Wed Jun 14 16:35:18 2017 -0400 Fix #13819 by refactoring TypeEqOrigin.uo_thing The uo_thing field of TypeEqOrigin is used to track the "thing" (either term or type) that has the type (kind) stored in the TypeEqOrigin fields. Previously, this was sometimes a proper Core Type, which needed zonking and tidying. Now, it is only HsSyn: much simpler, and the error messages now use the user-written syntax. But this aspect of uo_thing didn't cause #13819; it was the sibling field uo_arity that did. uo_arity stored the number of arguments of uo_thing, useful when reporting something like "should have written 2 fewer arguments". We wouldn't want to say that if the thing didn't have two arguments. However, in practice, GHC was getting this wrong, and this message didn't seem all that helpful. Furthermore, the calculation of the number of arguments is what caused #13819 to fall over. This patch just removes uo_arity. In my opinion, the change to error messages is a nudge in the right direction. Test case: typecheck/should_fail/T13819 >--------------------------------------------------------------- ea325787959da884a23f45f405bf9e3ee6329f59 compiler/ghci/RtClosureInspect.hs | 4 +- compiler/typecheck/Inst.hs | 8 +- compiler/typecheck/TcArrows.hs | 2 +- compiler/typecheck/TcErrors.hs | 20 ++- compiler/typecheck/TcExpr.hs | 50 ++++---- compiler/typecheck/TcHsType.hs | 135 +++++++++++---------- compiler/typecheck/TcMType.hs | 30 +---- compiler/typecheck/TcPat.hs | 6 +- compiler/typecheck/TcRnTypes.hs | 21 +--- compiler/typecheck/TcSigs.hs | 4 +- compiler/typecheck/TcSplice.hs | 13 +- compiler/typecheck/TcSplice.hs-boot | 6 +- compiler/typecheck/TcTyClsDecls.hs | 2 +- compiler/typecheck/TcType.hs | 7 ++ compiler/typecheck/TcUnify.hs | 65 +++++----- compiler/typecheck/TcUnify.hs-boot | 7 +- compiler/types/Type.hs | 2 +- .../tests/indexed-types/should_fail/T12867.stderr | 3 +- testsuite/tests/polykinds/T12593.stderr | 7 +- testsuite/tests/polykinds/T6039.stderr | 3 +- testsuite/tests/polykinds/T7278.stderr | 3 +- testsuite/tests/polykinds/T8616.stderr | 2 +- testsuite/tests/polykinds/T9200b.stderr | 6 +- .../tests/rename/should_fail/rnfail026.stderr | 3 +- testsuite/tests/th/T3177a.stderr | 6 +- .../tests/typecheck/should_fail/T11356.stderr | 3 +- .../tests/typecheck/should_fail/T11672.stderr | 11 +- .../tests/typecheck/should_fail/T12785b.stderr | 6 + testsuite/tests/typecheck/should_fail/T13819.hs | 14 +++ .../tests/typecheck/should_fail/T13819.stderr | 18 +++ testsuite/tests/typecheck/should_fail/T2994.stderr | 3 +- testsuite/tests/typecheck/should_fail/T3540.stderr | 2 +- testsuite/tests/typecheck/should_fail/T4875.stderr | 6 +- testsuite/tests/typecheck/should_fail/T7609.stderr | 11 +- testsuite/tests/typecheck/should_fail/T7778.stderr | 10 +- testsuite/tests/typecheck/should_fail/all.T | 1 + .../tests/typecheck/should_fail/tcfail070.stderr | 3 +- .../tests/typecheck/should_fail/tcfail078.stderr | 6 +- .../tests/typecheck/should_fail/tcfail113.stderr | 12 +- .../tests/typecheck/should_fail/tcfail123.stderr | 9 -- .../tests/typecheck/should_fail/tcfail132.stderr | 3 +- 41 files changed, 243 insertions(+), 290 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 ea325787959da884a23f45f405bf9e3ee6329f59 From git at git.haskell.org Wed Jul 19 12:03:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 12:03:59 +0000 (UTC) Subject: [commit: ghc] wip/rae: Track visibility in TypeEqOrigin (4931f56) Message-ID: <20170719120359.7F0BF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/4931f56b67f8abed01ab741d125d01c7012122c1/ghc >--------------------------------------------------------------- commit 4931f56b67f8abed01ab741d125d01c7012122c1 Author: Richard Eisenberg Date: Tue Jul 18 14:30:40 2017 -0400 Track visibility in TypeEqOrigin A type equality error can arise from a mismatch between *invisible* arguments just as easily as from visible arguments. But we should really prefer printing out errors from visible arguments over invisible ones. Suppose we have a mismatch between `Proxy Int` and `Proxy Maybe`. Would you rather get an error between `Int` and `Maybe`? Or between `*` and `* -> *`? I thought so, too. There is a fair amount of plumbing with this one, but I think it's worth it. >--------------------------------------------------------------- 4931f56b67f8abed01ab741d125d01c7012122c1 compiler/typecheck/Inst.hs | 3 +- compiler/typecheck/TcCanonical.hs | 18 +++-- compiler/typecheck/TcErrors.hs | 29 ++++---- compiler/typecheck/TcHsType.hs | 5 +- compiler/typecheck/TcRnTypes.hs | 30 ++++++++- compiler/typecheck/TcType.hs | 38 ++++++++++- compiler/typecheck/TcUnify.hs | 78 +++++++++++++--------- testsuite/tests/polykinds/KindVType.stderr | 2 +- .../tests/typecheck/should_fail/T12373.stderr | 3 + .../tests/typecheck/should_fail/T13530.stderr | 3 + testsuite/tests/typecheck/should_fail/T8603.stderr | 7 +- 11 files changed, 150 insertions(+), 66 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 4931f56b67f8abed01ab741d125d01c7012122c1 From git at git.haskell.org Wed Jul 19 12:04:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 12:04:05 +0000 (UTC) Subject: [commit: ghc] wip/rae: Document that type holes kill polymorphic recursion (572b076) Message-ID: <20170719120405.8AB5A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/572b076d354c38ab61e9b97050f46c51549df8f2/ghc >--------------------------------------------------------------- commit 572b076d354c38ab61e9b97050f46c51549df8f2 Author: Richard Eisenberg Date: Tue Jul 18 15:55:21 2017 -0400 Document that type holes kill polymorphic recursion This "fixes" #11995. >--------------------------------------------------------------- 572b076d354c38ab61e9b97050f46c51549df8f2 docs/users_guide/glasgow_exts.rst | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 6d53d25..f61ba86 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -10285,6 +10285,10 @@ warnings instead of errors. Additionally, these warnings can be silenced with the :ghc-flag:`-Wno-partial-type-signatures <-Wpartial-type-signatures>` flag. +However, because GHC must *infer* the type when part of a type is left +out, it is unable to use polymorphic recursion. The same restriction +takes place when the type signature is omitted completely. + .. _pts-syntax: Syntax From git at git.haskell.org Wed Jul 19 12:04:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 12:04:02 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #11963 by checking for more mixed type/kinds (7623d40) Message-ID: <20170719120402.BD4953A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/7623d40950f36c4275451459fb5825365c391e51/ghc >--------------------------------------------------------------- commit 7623d40950f36c4275451459fb5825365c391e51 Author: Richard Eisenberg Date: Tue Jul 18 15:49:38 2017 -0400 Fix #11963 by checking for more mixed type/kinds This is a straightforward fix -- there were just some omitted checks. test case: typecheck/should_fail/T11963 >--------------------------------------------------------------- 7623d40950f36c4275451459fb5825365c391e51 compiler/rename/RnTypes.hs | 25 +++++++++++++++---- testsuite/tests/typecheck/should_fail/T11963.hs | 29 ++++++++++++++++++++++ .../tests/typecheck/should_fail/T11963.stderr | 20 +++++++++++++++ testsuite/tests/typecheck/should_fail/all.T | 2 +- 4 files changed, 70 insertions(+), 6 deletions(-) diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs index 014d485..a0ceb32 100644 --- a/compiler/rename/RnTypes.hs +++ b/compiler/rename/RnTypes.hs @@ -1717,11 +1717,25 @@ extract_hs_tv_bndrs tvs = do { FKTV bndr_kvs _ <- foldrM extract_lkind emptyFKTV [k | L _ (KindedTyVar _ k) <- tvs] - ; let locals = map hsLTyVarName tvs + ; let locals = map hsLTyVarLocName tvs + + -- These checks are all tested in typecheck/should_fail/T11963 + ; check_for_mixed_vars bndr_kvs acc_tvs + ; check_for_mixed_vars bndr_kvs body_tvs + ; check_for_mixed_vars body_tvs acc_kvs + ; check_for_mixed_vars body_kvs acc_tvs + ; check_for_mixed_vars locals body_kvs + ; return $ - FKTV (filterOut ((`elem` locals) . unLoc) (bndr_kvs ++ body_kvs) + FKTV (filterOut (`elemRdr` locals) (bndr_kvs ++ body_kvs) ++ acc_kvs) - (filterOut ((`elem` locals) . unLoc) body_tvs ++ acc_tvs) } + (filterOut (`elemRdr` locals) body_tvs ++ acc_tvs) } + where + check_for_mixed_vars :: [Located RdrName] -> [Located RdrName] -> RnM () + check_for_mixed_vars tvs1 tvs2 = mapM_ check tvs1 + where + check tv1 = when (isRdrTyVar (unLoc tv1) && (tv1 `elemRdr` tvs2)) $ + mixedVarsErr tv1 extract_tv :: TypeOrKind -> Located RdrName -> FreeKiTyVars -> RnM FreeKiTyVars @@ -1737,8 +1751,6 @@ extract_tv t_or_k ltv@(L _ tv) acc mixedVarsErr ltv ; return (FKTV (ltv : kvs) tvs) } | otherwise = return acc - where - elemRdr x = any (eqLocated x) mixedVarsErr :: Located RdrName -> RnM () mixedVarsErr (L loc tv) @@ -1751,3 +1763,6 @@ mixedVarsErr (L loc tv) -- just used in this module; seemed convenient here nubL :: Eq a => [Located a] -> [Located a] nubL = nubBy eqLocated + +elemRdr :: Located RdrName -> [Located RdrName] -> Bool +elemRdr x = any (eqLocated x) diff --git a/testsuite/tests/typecheck/should_fail/T11963.hs b/testsuite/tests/typecheck/should_fail/T11963.hs new file mode 100644 index 0000000..c4f78ae --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T11963.hs @@ -0,0 +1,29 @@ +{-# LANGUAGE GADTs, PolyKinds, RankNTypes #-} + +module T11963 where + +-- this module should be rejected without TypeInType + +import Data.Proxy + +-- see code in RnTypes.extract_hs_tv_bndrs which checks for these bad cases + + -- bndr_kvs vs body_tvs +data Typ k t where + Typ :: (forall (a :: k -> *). a t -> a t) -> Typ k t + + -- bndr_kvs vs acc_tvs +foo :: (forall (t :: k). Proxy t) -> Proxy k +foo _ = undefined + + -- locals vs body_kvs +bar :: forall k. forall (t :: k). Proxy t +bar = undefined + + -- body_kvs vs acc_tvs +quux :: (forall t. Proxy (t :: k)) -> Proxy k +quux _ = undefined + + -- body_tvs vs acc_kvs +blargh :: (forall a. a -> Proxy k) -> Proxy (t :: k) +blargh _ = undefined diff --git a/testsuite/tests/typecheck/should_fail/T11963.stderr b/testsuite/tests/typecheck/should_fail/T11963.stderr new file mode 100644 index 0000000..74c3ab0 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T11963.stderr @@ -0,0 +1,20 @@ + +T11963.hs:13:26: error: + Variable ‘k’ used as both a kind and a type + Did you intend to use TypeInType? + +T11963.hs:16:22: error: + Variable ‘k’ used as both a kind and a type + Did you intend to use TypeInType? + +T11963.hs:20:15: error: + Variable ‘k’ used as both a kind and a type + Did you intend to use TypeInType? + +T11963.hs:24:32: error: + Variable ‘k’ used as both a kind and a type + Did you intend to use TypeInType? + +T11963.hs:28:33: error: + Variable ‘k’ used as both a kind and a type + Did you intend to use TypeInType? diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index f05d9d3..8c2c30f 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -450,4 +450,4 @@ test('T12373', normal, compile_fail, ['']) test('T13610', normal, compile_fail, ['']) test('T11672', normal, compile_fail, ['']) test('T13819', normal, compile_fail, ['']) - +test('T11963', normal, compile_fail, ['']) From git at git.haskell.org Wed Jul 19 12:04:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 12:04:08 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #12176 by being a bit more careful instantiating. (ba0598b) Message-ID: <20170719120408.C2C6B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/ba0598b791359fb72e5c7c588ba0d5bcfcda1c42/ghc >--------------------------------------------------------------- commit ba0598b791359fb72e5c7c588ba0d5bcfcda1c42 Author: Richard Eisenberg Date: Tue Jul 18 19:44:17 2017 -0400 Fix #12176 by being a bit more careful instantiating. Previously, looking up a TyCon that said "no" to mightBeUnsaturated would then instantiate all of its invisible binders. But this is wrong for vanilla type synonyms, whose RHS kind might legitimately start with invisible binders. So a little more care is taken now, only to instantiate those invisible binders that need to be (so that the TyCon isn't unsaturated). >--------------------------------------------------------------- ba0598b791359fb72e5c7c588ba0d5bcfcda1c42 compiler/typecheck/TcCanonical.hs | 4 +- compiler/typecheck/TcHsType.hs | 50 ++++++++++++++-------- testsuite/tests/dependent/should_compile/T12176.hs | 18 ++++++++ testsuite/tests/dependent/should_compile/all.T | 1 + 4 files changed, 53 insertions(+), 20 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index e38c045..cb2becd 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -24,7 +24,7 @@ import FamInstEnv ( FamInstEnvs ) import FamInst ( tcTopNormaliseNewTypeTF_maybe ) import Var import VarEnv( mkInScopeSet ) -import VarSet( extendVarSetList ) +import VarSet import Outputable import DynFlags( DynFlags ) import NameSet @@ -683,7 +683,7 @@ can_eq_nc_forall ev eq_rel s1 s2 go _ _ _ = panic "cna_eq_nc_forall" -- case (s:ss) [] empty_subst2 = mkEmptyTCvSubst $ mkInScopeSet $ - free_tvs2 `extendVarSetList` skol_tvs + free_tvs2 `unionVarSet` closeOverKinds (mkVarSet skol_tvs) ; (implic, _ev_binds, all_co) <- buildImplication skol_info skol_tvs [] $ go skol_tvs empty_subst2 bndrs2 diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 205224c..a2e98a8 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -922,30 +922,42 @@ checkExpectedKind hs_ty ty act_kind exp_kind , TcKind ) -- its new kind instantiate ty act_ki exp_ki = let (exp_bndrs, _) = splitPiTysInvisible exp_ki in - instantiateTyN (length exp_bndrs) ty act_ki - --- | Instantiate a type to have at most @n@ invisible arguments. -instantiateTyN :: Int -- ^ @n@ - -> TcType -- ^ the type - -> TcKind -- ^ its kind - -> TcM (TcType, TcKind) -- ^ The inst'ed type with kind -instantiateTyN n ty ki - = let (bndrs, inner_ki) = splitPiTysInvisible ki - num_to_inst = length bndrs - n - -- NB: splitAt is forgiving with invalid numbers - (inst_bndrs, leftover_bndrs) = splitAt num_to_inst bndrs + instantiateTyUntilN (length exp_bndrs) ty act_ki + +-- | Instantiate @n@ invisible arguments to a type. If @n <= 0@, no instantiation +-- occurs. If @n@ is too big, then all available invisible arguments are instantiated. +-- (In other words, this function is very forgiving about bad values of @n at .) +instantiateTyN :: Int -- ^ @n@ + -> TcType -- ^ the type + -> [TyBinder] -> TcKind -- ^ its kind + -> TcM (TcType, TcKind) -- ^ The inst'ed type with kind +instantiateTyN n ty bndrs inner_ki + = let -- NB: splitAt is forgiving with invalid numbers + (inst_bndrs, leftover_bndrs) = splitAt n bndrs + ki = mkPiTys bndrs inner_ki empty_subst = mkEmptyTCvSubst (mkInScopeSet (tyCoVarsOfType ki)) in - if num_to_inst <= 0 then return (ty, ki) else + if n <= 0 then return (ty, ki) else do { (subst, inst_args) <- tcInstBinders empty_subst Nothing inst_bndrs ; let rebuilt_ki = mkPiTys leftover_bndrs inner_ki ki' = substTy subst rebuilt_ki ; traceTc "instantiateTyN" (vcat [ ppr ty <+> dcolon <+> ppr ki + , ppr n , ppr subst , ppr rebuilt_ki , ppr ki' ]) ; return (mkNakedAppTys ty inst_args, ki') } +-- | Instantiate a type to have at most @n@ invisible arguments. +instantiateTyUntilN :: Int -- ^ @n@ + -> TcType -- ^ the type + -> TcKind -- ^ its kind + -> TcM (TcType, TcKind) -- ^ The inst'ed type with kind +instantiateTyUntilN n ty ki + = let (bndrs, inner_ki) = splitPiTysInvisible ki + num_to_inst = length bndrs - n + in + instantiateTyN num_to_inst ty bndrs inner_ki --------------------------- tcHsContext :: LHsContext GhcRn -> TcM [PredType] @@ -1018,8 +1030,8 @@ tcTyVar mode name -- Could be a tyvar, a tycon, or a datacon -- if we are type-checking a type family tycon, we must instantiate -- any invisible arguments right away. Otherwise, we get #11246 - handle_tyfams :: TyCon -- the tycon to instantiate (might be loopy) - -> TyCon -- a non-loopy version of the tycon + handle_tyfams :: TyCon -- the tycon to instantiate (might be loopy) + -> TcTyCon -- a non-loopy version of the tycon -> TcM (TcType, TcKind) handle_tyfams tc tc_tc | mightBeUnsaturatedTyCon tc_tc @@ -1027,7 +1039,8 @@ tcTyVar mode name -- Could be a tyvar, a tycon, or a datacon ; return (ty, tc_kind) } | otherwise - = do { (tc_ty, kind) <- instantiateTyN 0 ty tc_kind + = do { (tc_ty, kind) <- instantiateTyN (length (tyConBinders tc_tc)) + ty tc_kind_bndrs tc_inner_ki -- tc and tc_ty must not be traced here, because that would -- force the evaluation of a potentially knot-tied variable (tc), -- and the typechecker would hang, as per #11708 @@ -1035,8 +1048,9 @@ tcTyVar mode name -- Could be a tyvar, a tycon, or a datacon , ppr kind ]) ; return (tc_ty, kind) } where - ty = mkNakedTyConApp tc [] - tc_kind = tyConKind tc_tc + ty = mkNakedTyConApp tc [] + tc_kind = tyConKind tc_tc + (tc_kind_bndrs, tc_inner_ki) = splitPiTysInvisible tc_kind get_loopy_tc :: Name -> TyCon -> TcM TyCon -- Return the knot-tied global TyCon if there is one diff --git a/testsuite/tests/dependent/should_compile/T12176.hs b/testsuite/tests/dependent/should_compile/T12176.hs new file mode 100644 index 0000000..0e34006 --- /dev/null +++ b/testsuite/tests/dependent/should_compile/T12176.hs @@ -0,0 +1,18 @@ +{-# LANGUAGE RankNTypes, TypeInType, GADTs, TypeFamilies #-} + +module T12176 where + +import Data.Kind + +data Proxy :: forall k. k -> Type where + MkProxy :: forall k (a :: k). Proxy a + +data X where + MkX :: forall (k :: Type) (a :: k). Proxy a -> X + +type Expr = (MkX :: forall (a :: Bool). Proxy a -> X) + +type family Foo (x :: forall (a :: k). Proxy a -> X) where + Foo (MkX :: forall (a :: k). Proxy a -> X) = (MkProxy :: Proxy k) + +type Bug = Foo Expr -- this failed with #12176 diff --git a/testsuite/tests/dependent/should_compile/all.T b/testsuite/tests/dependent/should_compile/all.T index 8a9b221..b854f1d 100644 --- a/testsuite/tests/dependent/should_compile/all.T +++ b/testsuite/tests/dependent/should_compile/all.T @@ -24,3 +24,4 @@ test('T11719', normal, compile, ['']) test('T11966', normal, compile, ['']) test('T12442', normal, compile, ['']) test('T13538', normal, compile, ['']) +test('T12176', normal, compile, ['']) From git at git.haskell.org Wed Jul 19 12:04:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 12:04:11 +0000 (UTC) Subject: [commit: ghc] wip/rae's head updated: Fix #12176 by being a bit more careful instantiating. (ba0598b) Message-ID: <20170719120411.A34263A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/rae' now includes: 430137c Add mapMG to allow making ModuleGraph abstract 9849403 base: Validate input in setNumCapabilities dc8e686 Fix the treatment of 'closed' definitions fda094d Provide way to build using existing C compiler on Windows. d6cecde Remove the Windows GCC driver. 559a0c5 Fix out-of-date comments in TyCoRep 8573100 Look through type synonyms in existential contexts when deriving Functor df32880 Typofix in Data.Type.Equality comments b9f9670 rts: Ensure that new capability count is > 0 e12ea39 rts: A bit of cleanup around the eventlog 04ca036 testsuite: Add testcase for #13822 ee9232524 Add fixity declaration for :~~: 23f47b1 Add T9630 bea18a0 Fix GCC 7 warning in the RTS 990928f Don't expose fingerprints from Type.Reflection 271e0f0 Add test cases for #13821 a9b62a3 configure: Look for objdump on OpenBSD and AIX 6a2264d cmm/CmmLayoutStack: avoid generating unnecessary reloads 564a31f Reword documentation region overlap documentation for copying mutable arrays 986deaa Add missing -Wdeprecations flag to the users guide 5c93df9 Improve comments on AbsBinds b1fa386 Fix note reference [ci skip] 6dd1257 UNREG: use __builtin___clear_cache where available 88263f9 base: Export Fingerprint accessors from Type.Reflection.Unsafe c85cd9b Show only the number of modules in ghci c8370a8 change filtering of variables in extract_hs_tv_bndrs (fixes #13782) c6fe403 Revert "UNREG: use __builtin___clear_cache where available" d1d3e98 rts: Suppress unused gcc_clear_cache warning 76769bd Revert "rts: Suppress unused gcc_clear_cache warning" a9bf7d4 Fix typo 34b7f63 UNREG: use __builtin___clear_cache where available 84cf095 compiler: Eliminate pprTrace in SPT entry addition codepath e13edee testsuite: Fix cabal01 test 398a444 Add fixity declaration for Data.List.NonEmpty.!! 3c4537e Fix pretty-printing of zero-argument lambda expressions 9077120 Use actual universal tvs in check for naughty record selectors 42eee6e Hoopl: remove dependency on Hoopl package faefa7e documentation: fix trac issue #12978 a48464a users guide: Rephrasing 904255e DWARF: Use .short to render half-machine-words 4bd4f56 rts: Always collect stats 86abe0e users-guide/debug-info: Fix incorrect DWARF tags b8f8736 base/inputReady: Whitespace cleanup 914962c Update docs to reflect changes to DeriveDataTypeable 9ef909d Allow bytecode interpreter to make unsafe foreign calls 12a3c39 testsuite: Add broken test for #13871 1346525 typecheck: Consider types containing coercions non-Typeable 1e47126 rts: Clarify whitehole logic in threadPaused 6567c81 Treat banged bindings as FunBinds b070858 Make module membership on ModuleGraph faster 22b917e Revert "Make module membership on ModuleGraph faster" 4bdac33 Fix the in-scope set in TcHsType.instantiateTyN c80920d Do zonking in tcLHsKindSig fae672f Fix constraint solving for forall-types 87c5fdb Zap stable unfoldings in worker/wrapper 78c80c2 Typos in comments and manual [ci skip] 3f9422c More typos in comments [ci skip] 7097f94 Remove unneeded import 54ccf0c remove dead function 'tcInstBinders' 3b0e755 Fix lexically-scoped type variables 58c781d Revert "Remove the Windows GCC driver." c2fb6e8 Typos in comments c3f12ec Fix T13701 allocation for Linux 7de2c07 users-guide: Document FFI safety guarantees 6171b0b configure: Check for binutils #17166 007f255 Allow optional instance keyword in associated type family instances 625143f configure: Coerce gcc to use $LD instead of system default 9b514de rts/RetainerProfile: Const-correctness fixes 1ef4156 Prevent ApplicativeDo from applying to strict pattern matches (#13875) 0592318 Fix paper link in MVar docs [ci skip] 544ac0d rename tcInstBinder(s)X to tcInstBinder(s) 84d6831a users-guide: Wibbles in shared libraries discussion 287a405 Allow per-argument documentation on pattern synonym signatures 1a9c3c4 Implement recompilation checking for -fignore-asserts f9c6d53 Tag the FUN before making a PAP (#13767) c3a7862 Fix #13311 by using tcSplitNestedSigmaTys in the right place d55bea1 Fix -fno-code for modules that use -XQuasiQuotes 0c1f905 CmmParse: Emit source notes for assignments 5aee331 Bump array submodule to v0.5.2.0 8f8d756 rts: Fix uninitialised variable uses af403b2 ApplicativeDo: document behaviour with strict patterns (#13875) ef63ff2 configure: Remove --with-curses-includes flag a6f3d1b rts: Fix isByteArrayPinned#'s treatment of large arrays 960918b Add -fuse-ld flag to CFLAGS during configure 0836bfb testsuite: Add testcase for #13615 fd7a7a6 Eagerly blackhole AP_STACKs 9492703 rts/sm/Storage.c: tweak __clear_cache proto for clang 7040660 Revert "rts/sm/Storage.c: tweak __clear_cache proto for clang" 3eeb55e rts/sm/Storage.c: tweak __clear_cache proto for clang 555e5cc rts: Address AP_STACK comment suggestion from Simon 4997177 mkDocs: Don't install *.ps f3979b7 lowercase clang 99adcc8 Typos in comments [ci skip] bd4fdc6 Implement split-sections support for windows. c2303df aclocal.m4: allow arbitrary string in toolchain triplets e1146ed Fix typos in Bag.hs [ci skip] 81377e9 Big-obj support for the Windows runtime linker c506f83 Pretty-printer no longer butchers function arrow fixity 4f69013 testsuite: Decrease T13701 allocations 31ceaba user-guide: Various fixes to FFI section 905dc8b Make ':info Coercible' display an arbitrary string (fixes #12390) 7c9e356 Fix Work Balance computation in RTS stats b0c9f34 Improve Wmissing-home-modules warning under Cabal 6cff2ca Add testcase for T13818 15fcd9a Suppress unused warnings for selectors for some derived classes cb8db9b Sort list of failed tests for easier comparison between runs b8f33bc Always allow -staticlib fe6618b ByteCodeGen: use depth instead of offsets in BCEnv ccb849f users-guide/rel-notes: Describe #13875 fix 81de42c Add Template Haskell support for overloaded labels abda03b Optimize TimerManager ea75124 Fix logic error in GhcMake.enableCodeGenForTH ba46e63 Fix #13948 by being pickier about when to suggest DataKinds 85ac65c Fix #13947 by checking for unbounded names more ef7fd0a Parenthesize infix type names in data declarations in TH printer ec351b8 Add Template Haskell support for overloaded labels a249e93 Remove unnecessarily returned res_ty from rejigConRes d3bdd6c testsuite: Fix T13701 allocations yet again fcd2db1 configure: Ensure that we don't set LD to unusable linker be04c16 StgLint: Don't loop on tycons with runtime rep arguments 20880b5 testsuite: Show stderr output on command failure a0d9169 Fix minor typo 3a163aa Remove redundant import; fix note 4befb41 Mention which -Werror promoted a warning to an error 9b9f978 Use correct section types syntax for architecture 1ee49cb Fix missing escape in macro 60ec8f7 distrib/configure: Fail if we can't detect machine's word size 7ae4a28 [iserv] Fixing the word size for RemotePtr and toWordArray 5743581 testsuite: Update haddock allocations 4700baa testsuite: Again update allocations of T13701 1909985 Fix some excessive spacing in error messages f656fba [skip ci] Temporarily disable split-sections on Windows. 12ae1fa Fix a missing getNewNursery(), and related cleanup 935acb6 Typos in comments and explanation for unusused imports b8fec69 Make module membership on ModuleGraph faster c17d73c Improve error messages around kind mismatches. 4e96906 Fix #11400, #11560 by documenting an infelicity. 4a6a690 Test #11672 in typecheck/should_fail/T11672. 77c8e72 Don't tidy vars when dumping a type 4e45b23 Preserve CoVar uniques during pretty printing dfd2d39 Remove old coercion pretty-printer ea32578 Fix #13819 by refactoring TypeEqOrigin.uo_thing 4931f56 Track visibility in TypeEqOrigin 7623d40 Fix #11963 by checking for more mixed type/kinds 572b076 Document that type holes kill polymorphic recursion ba0598b Fix #12176 by being a bit more careful instantiating. From git at git.haskell.org Wed Jul 19 21:16:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:16:27 +0000 (UTC) Subject: [commit: packages/process] branch 'fix-appveyor' created Message-ID: <20170719211627.197D43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process New branch : fix-appveyor Referencing: 645b644b177206e0ad61d9b49f06e07637541954 From git at git.haskell.org Wed Jul 19 21:16:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:16:29 +0000 (UTC) Subject: [commit: packages/process] branch 'binary-handles' created Message-ID: <20170719211629.19F603A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process New branch : binary-handles Referencing: 982494d3e9b469900c4d794964e90268f9cb2fc8 From git at git.haskell.org Wed Jul 19 21:16:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:16:33 +0000 (UTC) Subject: [commit: packages/process] tag 'v1.6.0.0' created Message-ID: <20170719211633.1BE613A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process New tag : v1.6.0.0 Referencing: 8eeff78de2626c38919f80c3abf2cf4fa1cf0398 From git at git.haskell.org Wed Jul 19 21:16:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:16:35 +0000 (UTC) Subject: [commit: packages/process] master: Add Show and Eq instances to CreateProcess, CmdSpce, and StdStream. (7c63c9f) Message-ID: <20170719211635.243E13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7c63c9f4656748b8e7896b3d09a5300f71ad77b2/process >--------------------------------------------------------------- commit 7c63c9f4656748b8e7896b3d09a5300f71ad77b2 Author: Evan Laforge Date: Fri Mar 18 20:26:33 2016 -0700 Add Show and Eq instances to CreateProcess, CmdSpce, and StdStream. >--------------------------------------------------------------- 7c63c9f4656748b8e7896b3d09a5300f71ad77b2 System/Process/Common.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/System/Process/Common.hs b/System/Process/Common.hs index 0c55ff1..3a35e94 100644 --- a/System/Process/Common.hs +++ b/System/Process/Common.hs @@ -98,7 +98,7 @@ data CreateProcess = CreateProcess{ -- Default: @Nothing@ -- -- @since 1.4.0.0 - } + } deriving (Show, Eq) data CmdSpec = ShellCommand String @@ -125,6 +125,7 @@ data CmdSpec -- see the -- -- for the Windows @SearchPath@ API. + deriving (Show, Eq) -- | construct a `ShellCommand` from a string literal @@ -141,6 +142,7 @@ data StdStream -- and newline translation mode (just -- like @Handle at s created by @openFile@). | NoStream -- ^ No stream handle will be passed + deriving (Eq, Show) -- ---------------------------------------------------------------------------- -- ProcessHandle type From git at git.haskell.org Wed Jul 19 21:16:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:16:31 +0000 (UTC) Subject: [commit: packages/process] branch 'better-travis2' created Message-ID: <20170719211631.1AE503A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process New branch : better-travis2 Referencing: 359a86538aa855f967a521a5f8eb2497b81d04bd From git at git.haskell.org Wed Jul 19 21:16:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:16:37 +0000 (UTC) Subject: [commit: packages/process] better-travis2, binary-handles, fix-appveyor, master: Removed .hsc extension no longer in use (Process.hs) (20acf5a) Message-ID: <20170719211637.2A74A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: better-travis2,binary-handles,fix-appveyor,master Link : http://ghc.haskell.org/trac/ghc/changeset/20acf5a608007817ce7b4efe41305dc98dc409e2/process >--------------------------------------------------------------- commit 20acf5a608007817ce7b4efe41305dc98dc409e2 Author: Robert Henderson Date: Thu May 12 09:59:59 2016 +0100 Removed .hsc extension no longer in use (Process.hs) >--------------------------------------------------------------- 20acf5a608007817ce7b4efe41305dc98dc409e2 System/{Process.hsc => Process.hs} | 0 1 file changed, 0 insertions(+), 0 deletions(-) diff --git a/System/Process.hsc b/System/Process.hs similarity index 100% rename from System/Process.hsc rename to System/Process.hs From git at git.haskell.org Wed Jul 19 21:16:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:16:39 +0000 (UTC) Subject: [commit: packages/process] better-travis2, binary-handles, fix-appveyor, master: Merge pull request #62 from robjhen/master (8230f33) Message-ID: <20170719211639.3099D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: better-travis2,binary-handles,fix-appveyor,master Link : http://ghc.haskell.org/trac/ghc/changeset/8230f3386e5ff9e06549e0a16899e24770c1a2ad/process >--------------------------------------------------------------- commit 8230f3386e5ff9e06549e0a16899e24770c1a2ad Merge: 296cbce 20acf5a Author: Michael Snoyman Date: Thu May 12 18:13:41 2016 +0300 Merge pull request #62 from robjhen/master Removed .hsc extension no longer in use >--------------------------------------------------------------- 8230f3386e5ff9e06549e0a16899e24770c1a2ad System/{Process.hsc => Process.hs} | 0 1 file changed, 0 insertions(+), 0 deletions(-) From git at git.haskell.org Wed Jul 19 21:16:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:16:41 +0000 (UTC) Subject: [commit: packages/process] better-travis2, binary-handles, fix-appveyor, master: Close pipes on failure (a9a8e91) Message-ID: <20170719211641.36D0B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: better-travis2,binary-handles,fix-appveyor,master Link : http://ghc.haskell.org/trac/ghc/changeset/a9a8e914e114913f5eea07da607b29c137bf2041/process >--------------------------------------------------------------- commit a9a8e914e114913f5eea07da607b29c137bf2041 Author: Yuras Shumovich Date: Thu May 26 13:46:21 2016 +0300 Close pipes on failure Make sure stdin, stdout and stderr pipes are closed when exec call fails, e.g. when the executable doesn't exist. >--------------------------------------------------------------- a9a8e914e114913f5eea07da607b29c137bf2041 cbits/runProcess.c | 25 +++++++++++++++++++++++++ 1 file changed, 25 insertions(+) diff --git a/cbits/runProcess.c b/cbits/runProcess.c index 950635d..02dea87 100644 --- a/cbits/runProcess.c +++ b/cbits/runProcess.c @@ -84,6 +84,10 @@ runInteractiveProcess (char *const args[], if (fdStdOut == -1) { r = pipe(fdStdOutput); if (r == -1) { + if (fdStdIn == -1) { + close(fdStdInput[0]); + close(fdStdInput[1]); + } *failed_doing = "runInteractiveProcess: pipe"; return -1; } @@ -92,6 +96,14 @@ runInteractiveProcess (char *const args[], r = pipe(fdStdError); if (r == -1) { *failed_doing = "runInteractiveProcess: pipe"; + if (fdStdIn == -1) { + close(fdStdInput[0]); + close(fdStdInput[1]); + } + if (fdStdOut == -1) { + close(fdStdOutput[0]); + close(fdStdOutput[1]); + } return -1; } } @@ -328,6 +340,19 @@ runInteractiveProcess (char *const args[], // our responsibility to reap here as nobody else can. waitpid(pid, NULL, 0); + if (fdStdIn == -1) { + close(fdStdInput[0]); + close(fdStdInput[1]); + } + if (fdStdOut == -1) { + close(fdStdOutput[0]); + close(fdStdOutput[1]); + } + if (fdStdErr == -1) { + close(fdStdError[0]); + close(fdStdError[1]); + } + pid = -1; } else if (r != 0) { From git at git.haskell.org Wed Jul 19 21:16:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:16:43 +0000 (UTC) Subject: [commit: packages/process] better-travis2, binary-handles, fix-appveyor, master: Merge pull request #65 from Yuras/pipe_leak (a09ec12) Message-ID: <20170719211643.3D6D43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: better-travis2,binary-handles,fix-appveyor,master Link : http://ghc.haskell.org/trac/ghc/changeset/a09ec12d63db42be10f8e6d16c40d8cf13aaee00/process >--------------------------------------------------------------- commit a09ec12d63db42be10f8e6d16c40d8cf13aaee00 Merge: 8230f33 a9a8e91 Author: Michael Snoyman Date: Tue Jun 14 14:55:23 2016 +0300 Merge pull request #65 from Yuras/pipe_leak Close pipes on failure >--------------------------------------------------------------- a09ec12d63db42be10f8e6d16c40d8cf13aaee00 cbits/runProcess.c | 25 +++++++++++++++++++++++++ 1 file changed, 25 insertions(+) From git at git.haskell.org Wed Jul 19 21:16:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:16:45 +0000 (UTC) Subject: [commit: packages/process] binary-handles: Add check for binary handles (982494d) Message-ID: <20170719211645.43C033A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : binary-handles Link : http://ghc.haskell.org/trac/ghc/changeset/982494d3e9b469900c4d794964e90268f9cb2fc8/process >--------------------------------------------------------------- commit 982494d3e9b469900c4d794964e90268f9cb2fc8 Author: Michael Snoyman Date: Tue Jun 14 16:37:39 2016 +0300 Add check for binary handles >--------------------------------------------------------------- 982494d3e9b469900c4d794964e90268f9cb2fc8 process.cabal | 2 ++ test/main.hs | 26 ++++++++++++++++++++++++++ 2 files changed, 28 insertions(+) diff --git a/process.cabal b/process.cabal index 15f6a65..3c51883 100644 --- a/process.cabal +++ b/process.cabal @@ -77,4 +77,6 @@ test-suite test main-is: main.hs type: exitcode-stdio-1.0 build-depends: base + , bytestring + , directory , process diff --git a/test/main.hs b/test/main.hs index 40558b2..c5ba671 100644 --- a/test/main.hs +++ b/test/main.hs @@ -1,7 +1,12 @@ import Control.Exception +import Control.Monad (unless) import System.Exit import System.IO.Error import System.Process +import System.IO (hClose, openBinaryTempFile) +import qualified Data.ByteString as S +import qualified Data.ByteString.Char8 as S8 +import System.Directory (getTemporaryDirectory, removeFile) main :: IO () main = do @@ -27,4 +32,25 @@ main = do test "create_new_console" $ \cp -> cp { create_new_console = True } test "new_session" $ \cp -> cp { new_session = True } + putStrLn "Binary handles" + tmpDir <- getTemporaryDirectory + bracket + (openBinaryTempFile tmpDir "process-binary-test.bin") + (\(fp, h) -> hClose h `finally` removeFile fp) + $ \(fp, h) -> do + let bs = S8.pack "hello\nthere\r\nworld\0" + S.hPut h bs + hClose h + + (Nothing, Just out, Nothing, ph) <- createProcess (proc "cat" [fp]) + { std_out = CreatePipe + } + res <- S.hGetContents out + hClose out + ec <- waitForProcess ph + unless (ec == ExitSuccess) + $ error $ "Unexpected exit code " ++ show ec + unless (bs == res) + $ error $ "Unexpected result: " ++ show res + putStrLn "Tests passed successfully" From git at git.haskell.org Wed Jul 19 21:16:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:16:49 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #67 from haskell/binary-handles (5616568) Message-ID: <20170719211649.51BAB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5616568ddbb48274e6b4759d966b79cd9f9e5dcc/process >--------------------------------------------------------------- commit 5616568ddbb48274e6b4759d966b79cd9f9e5dcc Merge: a09ec12 68abdc2 Author: Michael Snoyman Date: Tue Jun 14 18:00:03 2016 +0300 Merge pull request #67 from haskell/binary-handles Add check for binary handles >--------------------------------------------------------------- 5616568ddbb48274e6b4759d966b79cd9f9e5dcc process.cabal | 2 ++ test/main.hs | 26 ++++++++++++++++++++++++++ 2 files changed, 28 insertions(+) From git at git.haskell.org Wed Jul 19 21:16:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:16:47 +0000 (UTC) Subject: [commit: packages/process] master: Add check for binary handles (68abdc2) Message-ID: <20170719211647.4A2DB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/68abdc2af6272c3d8531ba26482d6b38052d7d33/process >--------------------------------------------------------------- commit 68abdc2af6272c3d8531ba26482d6b38052d7d33 Author: Michael Snoyman Date: Tue Jun 14 16:37:39 2016 +0300 Add check for binary handles >--------------------------------------------------------------- 68abdc2af6272c3d8531ba26482d6b38052d7d33 process.cabal | 2 ++ test/main.hs | 26 ++++++++++++++++++++++++++ 2 files changed, 28 insertions(+) diff --git a/process.cabal b/process.cabal index 15f6a65..3c51883 100644 --- a/process.cabal +++ b/process.cabal @@ -77,4 +77,6 @@ test-suite test main-is: main.hs type: exitcode-stdio-1.0 build-depends: base + , bytestring + , directory , process diff --git a/test/main.hs b/test/main.hs index 40558b2..65c0342 100644 --- a/test/main.hs +++ b/test/main.hs @@ -1,7 +1,12 @@ import Control.Exception +import Control.Monad (unless) import System.Exit import System.IO.Error import System.Process +import System.IO (hClose, openBinaryTempFile) +import qualified Data.ByteString as S +import qualified Data.ByteString.Char8 as S8 +import System.Directory (getTemporaryDirectory, removeFile) main :: IO () main = do @@ -27,4 +32,25 @@ main = do test "create_new_console" $ \cp -> cp { create_new_console = True } test "new_session" $ \cp -> cp { new_session = True } + putStrLn "Binary handles" + tmpDir <- getTemporaryDirectory + bracket + (openBinaryTempFile tmpDir "process-binary-test.bin") + (\(fp, h) -> hClose h `finally` removeFile fp) + $ \(fp, h) -> do + let bs = S8.pack "hello\nthere\r\nworld\0" + S.hPut h bs + hClose h + + (Nothing, Just out, Nothing, ph) <- createProcess (proc "cat" [fp]) + { std_out = CreatePipe + } + res' <- S.hGetContents out + hClose out + ec <- waitForProcess ph + unless (ec == ExitSuccess) + $ error $ "Unexpected exit code " ++ show ec + unless (bs == res') + $ error $ "Unexpected result: " ++ show res' + putStrLn "Tests passed successfully" From git at git.haskell.org Wed Jul 19 21:16:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:16:53 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #69 from JonCoens/withCreateProcess (18bb13c) Message-ID: <20170719211653.5F2B03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/18bb13c5a4e82dda51aa7bc8ebebebd750b69776/process >--------------------------------------------------------------- commit 18bb13c5a4e82dda51aa7bc8ebebebd750b69776 Merge: 5616568 2398a4c Author: Michael Snoyman Date: Thu Aug 11 19:40:12 2016 +0300 Merge pull request #69 from JonCoens/withCreateProcess Expose withCreateProcess to users. >--------------------------------------------------------------- 18bb13c5a4e82dda51aa7bc8ebebebd750b69776 System/Process.hs | 21 ++++++++++----------- changelog.md | 4 ++++ 2 files changed, 14 insertions(+), 11 deletions(-) From git at git.haskell.org Wed Jul 19 21:16:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:16:51 +0000 (UTC) Subject: [commit: packages/process] master: Expose withCreateProcess to users. (2398a4c) Message-ID: <20170719211651.5891F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2398a4ca5b6fb999db670d00f07eb8d89c524d1b/process >--------------------------------------------------------------- commit 2398a4ca5b6fb999db670d00f07eb8d89c524d1b Author: Jon Coens Date: Thu Aug 11 15:04:32 2016 +0100 Expose withCreateProcess to users. The function was commented out and not used anywhere. I changed it to run cleanup on more than just exceptional cases. >--------------------------------------------------------------- 2398a4ca5b6fb999db670d00f07eb8d89c524d1b System/Process.hs | 21 ++++++++++----------- changelog.md | 4 ++++ 2 files changed, 14 insertions(+), 11 deletions(-) diff --git a/System/Process.hs b/System/Process.hs index 37d442f..3b048b3 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -42,6 +42,7 @@ module System.Process ( readProcess, readCreateProcessWithExitCode, readProcessWithExitCode, + withCreateProcess, -- ** Related utilities showCommandForUser, @@ -196,29 +197,27 @@ createProcess cp = do maybeCloseStd _ = return () {- --- TODO: decide if we want to expose this to users --- | A 'C.bracketOnError'-style resource handler for 'createProcess'. +-- | A 'C.bracket'-style resource handler for 'createProcess'. -- --- In normal operation it adds nothing, you are still responsible for waiting --- for (or forcing) process termination and closing any 'Handle's. It only does --- automatic cleanup if there is an exception. If there is an exception in the --- body then it ensures that the process gets terminated and any 'CreatePipe' --- 'Handle's are closed. In particular this means that if the Haskell thread --- is killed (e.g. 'killThread'), that the external process is also terminated. +-- Does automatic cleanup when the action finishes. If there is an exception +-- in the body then it ensures that the process gets terminated and any +-- 'CreatePipe' 'Handle's are closed. In particular this means that if the +-- Haskell thread is killed (e.g. 'killThread'), that the external process is +-- also terminated. -- -- e.g. -- -- > withCreateProcess (proc cmd args) { ... } $ \_ _ _ ph -> do -- > ... -- +-} withCreateProcess :: CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a) -> IO a withCreateProcess c action = - C.bracketOnError (createProcess c) cleanupProcess - (\(m_in, m_out, m_err, ph) -> action m_in m_out m_err ph) --} + C.bracket (createProcess c) cleanupProcess + (\(m_in, m_out, m_err, ph) -> action m_in m_out m_err ph) -- wrapper so we can get exceptions with the appropriate function name. withCreateProcess_ diff --git a/changelog.md b/changelog.md index 7a220f7..fc27e26 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,9 @@ # Changelog for [`process` package](http://hackage.haskell.org/package/process) +## Unreleased + + * New exposed `withCreateProcess` + ## 1.4.2.0 *January 2016* * Added `createPipeFD` [#52](https://github.com/haskell/process/pull/52) From git at git.haskell.org Wed Jul 19 21:16:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:16:57 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #73 from erikd/master (8514798) Message-ID: <20170719211657.6CE983A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8514798f876c69159e5a99b2405938294d9e51b2/process >--------------------------------------------------------------- commit 8514798f876c69159e5a99b2405938294d9e51b2 Merge: 18bb13c f995e84 Author: Michael Snoyman Date: Sun Oct 23 07:34:03 2016 +0300 Merge pull request #73 from erikd/master Fix CPP usage >--------------------------------------------------------------- 8514798f876c69159e5a99b2405938294d9e51b2 System/Process/Internals.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Wed Jul 19 21:16:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:16:59 +0000 (UTC) Subject: [commit: packages/process] master: Add a remark on how relative cmdspec is resolved w.r.t. to cwd. (681aaee) Message-ID: <20170719211659.729A13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/681aaeedf8b3b28f57ff2b15074010dfdad173fe/process >--------------------------------------------------------------- commit 681aaeedf8b3b28f57ff2b15074010dfdad173fe Author: Edward Z. Yang Date: Fri Nov 11 09:34:12 2016 -0500 Add a remark on how relative cmdspec is resolved w.r.t. to cwd. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 681aaeedf8b3b28f57ff2b15074010dfdad173fe System/Process/Common.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Process/Common.hs b/System/Process/Common.hs index 0c55ff1..167ae61 100644 --- a/System/Process/Common.hs +++ b/System/Process/Common.hs @@ -64,7 +64,7 @@ type PHANDLE = CPid #endif data CreateProcess = CreateProcess{ - cmdspec :: CmdSpec, -- ^ Executable & arguments, or shell command + cmdspec :: CmdSpec, -- ^ Executable & arguments, or shell command. Relative paths are resolved with respect to 'cwd' if given, and otherwise the current working directory. cwd :: Maybe FilePath, -- ^ Optional path to the working directory for the new process env :: Maybe [(String,String)], -- ^ Optional environment (otherwise inherit from the current process) std_in :: StdStream, -- ^ How to determine stdin From git at git.haskell.org Wed Jul 19 21:16:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:16:55 +0000 (UTC) Subject: [commit: packages/process] master: Fix CPP usage (f995e84) Message-ID: <20170719211655.6586C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f995e843e2c5a771b1bcd8e9c68078387d7cefce/process >--------------------------------------------------------------- commit f995e843e2c5a771b1bcd8e9c68078387d7cefce Author: Erik de Castro Lopo Date: Sun Oct 23 12:55:32 2016 +1100 Fix CPP usage The code `#if WINDOWS` works but is not really correct. GHC HEAD now has a `-Wcpp-undef` warning that we would like to turn on and hence need this fixed. >--------------------------------------------------------------- f995e843e2c5a771b1bcd8e9c68078387d7cefce System/Process/Internals.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index c4d5be3..af42009 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -50,7 +50,7 @@ import System.Posix.Internals (FD) import System.Process.Common -#if WINDOWS +#ifdef WINDOWS import System.Process.Windows #else import System.Process.Posix From git at git.haskell.org Wed Jul 19 21:17:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:01 +0000 (UTC) Subject: [commit: packages/process] master: Test relative paths in subdirectories (fc06dff) Message-ID: <20170719211701.79D783A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fc06dff1986d7420190ecbb4a289f2f087a1671f/process >--------------------------------------------------------------- commit fc06dff1986d7420190ecbb4a289f2f087a1671f Author: Michael Snoyman Date: Sun Nov 13 11:38:04 2016 +0200 Test relative paths in subdirectories >--------------------------------------------------------------- fc06dff1986d7420190ecbb4a289f2f087a1671f exes/echo.bat | 1 + exes/subdir/echo.bat | 1 + process.cabal | 3 +++ test/main.hs | 21 +++++++++++++++++++++ 4 files changed, 26 insertions(+) diff --git a/exes/echo.bat b/exes/echo.bat new file mode 100755 index 0000000..2699c07 --- /dev/null +++ b/exes/echo.bat @@ -0,0 +1 @@ +echo parent diff --git a/exes/subdir/echo.bat b/exes/subdir/echo.bat new file mode 100755 index 0000000..52091e8 --- /dev/null +++ b/exes/subdir/echo.bat @@ -0,0 +1 @@ +echo child diff --git a/process.cabal b/process.cabal index ee79452..a0c72fb 100644 --- a/process.cabal +++ b/process.cabal @@ -19,6 +19,8 @@ extra-source-files: configure.ac include/HsProcessConfig.h.in process.buildinfo + exes/echo.bat + exes/subdir/echo.bat extra-tmp-files: autom4te.cache @@ -81,4 +83,5 @@ test-suite test main-is: main.hs type: exitcode-stdio-1.0 build-depends: base + , directory , process diff --git a/test/main.hs b/test/main.hs index 40558b2..c47838e 100644 --- a/test/main.hs +++ b/test/main.hs @@ -1,6 +1,8 @@ import Control.Exception +import Control.Monad (unless) import System.Exit import System.IO.Error +import System.Directory (getCurrentDirectory, setCurrentDirectory) import System.Process main :: IO () @@ -27,4 +29,23 @@ main = do test "create_new_console" $ \cp -> cp { create_new_console = True } test "new_session" $ \cp -> cp { new_session = True } + putStrLn "Testing subdirectories" + + withCurrentDirectory "exes" $ do + res <- readCreateProcess (proc "./echo.bat" []) "" + unless (res == "parent\n") $ error $ + "echo.bat with cwd failed: " ++ show res + + res <- readCreateProcess (proc "./echo.bat" []) { cwd = Just "subdir" } "" + unless (res == "child\n") $ error $ + "echo.bat with cwd failed: " ++ show res + putStrLn "Tests passed successfully" + +withCurrentDirectory :: FilePath -> IO a -> IO a +withCurrentDirectory new inner = do + orig <- getCurrentDirectory + bracket_ + (setCurrentDirectory new) + (setCurrentDirectory orig) + inner From git at git.haskell.org Wed Jul 19 21:17:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:03 +0000 (UTC) Subject: [commit: packages/process] master: Include -y to pacman (acb7d7b) Message-ID: <20170719211703.7FCDE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/acb7d7b0da8356f3b787b739804b3ae4f6fda842/process >--------------------------------------------------------------- commit acb7d7b0da8356f3b787b739804b3ae4f6fda842 Author: Michael Snoyman Date: Sun Nov 13 11:40:19 2016 +0200 Include -y to pacman >--------------------------------------------------------------- acb7d7b0da8356f3b787b739804b3ae4f6fda842 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 4117809..195e8e2 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -16,5 +16,5 @@ test_script: - stack setup > nul # The ugly echo "" hack is to avoid complaints about 0 being an invalid file # descriptor -- echo "" | stack exec -- sh -c "pacman -S autoconf && autoreconf -i" +- echo "" | stack exec -- sh -c "pacman -Sy autoconf && autoreconf -i" - echo "" | stack --no-terminal test --pedantic From git at git.haskell.org Wed Jul 19 21:17:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:05 +0000 (UTC) Subject: [commit: packages/process] master: Bump resolver (8cb9e18) Message-ID: <20170719211705.8692C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8cb9e18cc2b22c3b4b7f8bf9f929ef40341b1531/process >--------------------------------------------------------------- commit 8cb9e18cc2b22c3b4b7f8bf9f929ef40341b1531 Author: Michael Snoyman Date: Sun Nov 13 11:40:25 2016 +0200 Bump resolver >--------------------------------------------------------------- 8cb9e18cc2b22c3b4b7f8bf9f929ef40341b1531 stack.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/stack.yaml b/stack.yaml index eed5796..faded16 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1 +1 @@ -resolver: ghc-7.10.2 +resolver: ghc-7.10.3 From git at git.haskell.org Wed Jul 19 21:17:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:07 +0000 (UTC) Subject: [commit: packages/process] master: Fix warnings (f030349) Message-ID: <20170719211707.8C8B43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f0303495d28420cd990f10b724c7aaca9846a2e4/process >--------------------------------------------------------------- commit f0303495d28420cd990f10b724c7aaca9846a2e4 Author: Michael Snoyman Date: Sun Nov 13 11:41:32 2016 +0200 Fix warnings >--------------------------------------------------------------- f0303495d28420cd990f10b724c7aaca9846a2e4 test/main.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/test/main.hs b/test/main.hs index c47838e..be941f9 100644 --- a/test/main.hs +++ b/test/main.hs @@ -32,13 +32,13 @@ main = do putStrLn "Testing subdirectories" withCurrentDirectory "exes" $ do - res <- readCreateProcess (proc "./echo.bat" []) "" - unless (res == "parent\n") $ error $ - "echo.bat with cwd failed: " ++ show res + res1 <- readCreateProcess (proc "./echo.bat" []) "" + unless (res1 == "parent\n") $ error $ + "echo.bat with cwd failed: " ++ show res1 - res <- readCreateProcess (proc "./echo.bat" []) { cwd = Just "subdir" } "" - unless (res == "child\n") $ error $ - "echo.bat with cwd failed: " ++ show res + res2 <- readCreateProcess (proc "./echo.bat" []) { cwd = Just "subdir" } "" + unless (res2 == "child\n") $ error $ + "echo.bat with cwd failed: " ++ show res2 putStrLn "Tests passed successfully" From git at git.haskell.org Wed Jul 19 21:17:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:09 +0000 (UTC) Subject: [commit: packages/process] better-travis2, master: Better Travis: more GHCs, Stack, and OS X (359a865) Message-ID: <20170719211709.93BA03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: better-travis2,master Link : http://ghc.haskell.org/trac/ghc/changeset/359a86538aa855f967a521a5f8eb2497b81d04bd/process >--------------------------------------------------------------- commit 359a86538aa855f967a521a5f8eb2497b81d04bd Author: Michael Snoyman Date: Sun Nov 13 11:46:23 2016 +0200 Better Travis: more GHCs, Stack, and OS X >--------------------------------------------------------------- 359a86538aa855f967a521a5f8eb2497b81d04bd .travis.yml | 238 ++++++++++++++++++++++++++++++++++++++++++------------------ 1 file changed, 167 insertions(+), 71 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 359a86538aa855f967a521a5f8eb2497b81d04bd From git at git.haskell.org Wed Jul 19 21:17:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:11 +0000 (UTC) Subject: [commit: packages/process] fix-appveyor: appveyor: use -Syu (645b644) Message-ID: <20170719211711.9A20E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : fix-appveyor Link : http://ghc.haskell.org/trac/ghc/changeset/645b644b177206e0ad61d9b49f06e07637541954/process >--------------------------------------------------------------- commit 645b644b177206e0ad61d9b49f06e07637541954 Author: Michael Snoyman Date: Sun Nov 13 11:48:24 2016 +0200 appveyor: use -Syu >--------------------------------------------------------------- 645b644b177206e0ad61d9b49f06e07637541954 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 2c313d4..f3d7e2b 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -16,5 +16,5 @@ test_script: - stack setup > nul # The ugly echo "" hack is to avoid complaints about 0 being an invalid file # descriptor -- echo y | stack exec -- sh -c "pacman -Sy autoconf perl && autoreconf -i" +- echo y | stack exec -- sh -c "pacman -Syu autoconf perl && autoreconf -i" - echo "" | stack --no-terminal test --pedantic From git at git.haskell.org Wed Jul 19 21:17:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:13 +0000 (UTC) Subject: [commit: packages/process] master: Merge branch 'master' into 74-check-rel-path-subdirs (d661dda) Message-ID: <20170719211713.A34CE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d661ddaaabc9fee20e9f3ba772095b7c6eedc6ba/process >--------------------------------------------------------------- commit d661ddaaabc9fee20e9f3ba772095b7c6eedc6ba Merge: f030349 a09ec12 Author: Michael Snoyman Date: Sun Nov 13 11:50:14 2016 +0200 Merge branch 'master' into 74-check-rel-path-subdirs >--------------------------------------------------------------- d661ddaaabc9fee20e9f3ba772095b7c6eedc6ba .travis.yml | 130 +++++++++++++++++++++-------- README.md | 2 +- System/{Process.hsc => Process.hs} | 65 +-------------- System/Process/Internals.hs | 39 +++++++-- System/Process/Posix.hs | 23 ++++- System/Process/{Windows.hs => Windows.hsc} | 71 +++++++++++----- appveyor.yml | 2 +- cbits/runProcess.c | 25 ++++++ changelog.md | 12 +++ configure.ac | 5 +- process.cabal | 26 +++--- 11 files changed, 247 insertions(+), 153 deletions(-) From git at git.haskell.org Wed Jul 19 21:17:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:15 +0000 (UTC) Subject: [commit: packages/process] master: Use isInfixOf (for Windows) (1ffe7da) Message-ID: <20170719211715.A9EEE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1ffe7da7eed4aac042eb68fe06fdcfb8464668f5/process >--------------------------------------------------------------- commit 1ffe7da7eed4aac042eb68fe06fdcfb8464668f5 Author: Michael Snoyman Date: Sun Nov 13 11:55:47 2016 +0200 Use isInfixOf (for Windows) >--------------------------------------------------------------- 1ffe7da7eed4aac042eb68fe06fdcfb8464668f5 test/main.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/test/main.hs b/test/main.hs index be941f9..f768b81 100644 --- a/test/main.hs +++ b/test/main.hs @@ -4,6 +4,7 @@ import System.Exit import System.IO.Error import System.Directory (getCurrentDirectory, setCurrentDirectory) import System.Process +import Data.List (isInfixOf) main :: IO () main = do @@ -33,11 +34,11 @@ main = do withCurrentDirectory "exes" $ do res1 <- readCreateProcess (proc "./echo.bat" []) "" - unless (res1 == "parent\n") $ error $ + unless ("parent" `isInfixOf` res1) $ error $ "echo.bat with cwd failed: " ++ show res1 res2 <- readCreateProcess (proc "./echo.bat" []) { cwd = Just "subdir" } "" - unless (res2 == "child\n") $ error $ + unless ("child" `isInfixOf` res2) $ error $ "echo.bat with cwd failed: " ++ show res2 putStrLn "Tests passed successfully" From git at git.haskell.org Wed Jul 19 21:17:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:17 +0000 (UTC) Subject: [commit: packages/process] master: Merge branch 'master' of https://github.com/ezyang/process into 74-check-rel-path-subdirs (66eaeb6) Message-ID: <20170719211717.B1DF33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/66eaeb612ad64da2738e83f4eac24ca748a3ac64/process >--------------------------------------------------------------- commit 66eaeb612ad64da2738e83f4eac24ca748a3ac64 Merge: 1ffe7da 681aaee Author: Michael Snoyman Date: Sun Nov 13 12:01:39 2016 +0200 Merge branch 'master' of https://github.com/ezyang/process into 74-check-rel-path-subdirs >--------------------------------------------------------------- 66eaeb612ad64da2738e83f4eac24ca748a3ac64 System/Process.hs | 21 ++++++++++----------- System/Process/Common.hs | 2 +- System/Process/Internals.hs | 2 +- changelog.md | 4 ++++ process.cabal | 1 + test/main.hs | 25 +++++++++++++++++++++++++ 6 files changed, 42 insertions(+), 13 deletions(-) diff --cc test/main.hs index f768b81,65c0342..3bc6d8c --- a/test/main.hs +++ b/test/main.hs @@@ -2,9 -2,11 +2,13 @@@ import Control.Exceptio import Control.Monad (unless) import System.Exit import System.IO.Error +import System.Directory (getCurrentDirectory, setCurrentDirectory) import System.Process +import Data.List (isInfixOf) + import System.IO (hClose, openBinaryTempFile) + import qualified Data.ByteString as S + import qualified Data.ByteString.Char8 as S8 + import System.Directory (getTemporaryDirectory, removeFile) main :: IO () main = do @@@ -30,23 -32,25 +34,44 @@@ test "create_new_console" $ \cp -> cp { create_new_console = True } test "new_session" $ \cp -> cp { new_session = True } + putStrLn "Testing subdirectories" + + withCurrentDirectory "exes" $ do + res1 <- readCreateProcess (proc "./echo.bat" []) "" + unless ("parent" `isInfixOf` res1) $ error $ + "echo.bat with cwd failed: " ++ show res1 + + res2 <- readCreateProcess (proc "./echo.bat" []) { cwd = Just "subdir" } "" + unless ("child" `isInfixOf` res2) $ error $ + "echo.bat with cwd failed: " ++ show res2 + + putStrLn "Binary handles" + tmpDir <- getTemporaryDirectory + bracket + (openBinaryTempFile tmpDir "process-binary-test.bin") + (\(fp, h) -> hClose h `finally` removeFile fp) + $ \(fp, h) -> do + let bs = S8.pack "hello\nthere\r\nworld\0" + S.hPut h bs + hClose h + + (Nothing, Just out, Nothing, ph) <- createProcess (proc "cat" [fp]) + { std_out = CreatePipe + } + res' <- S.hGetContents out + hClose out + ec <- waitForProcess ph + unless (ec == ExitSuccess) + $ error $ "Unexpected exit code " ++ show ec + unless (bs == res') + $ error $ "Unexpected result: " ++ show res' + putStrLn "Tests passed successfully" + +withCurrentDirectory :: FilePath -> IO a -> IO a +withCurrentDirectory new inner = do + orig <- getCurrentDirectory + bracket_ + (setCurrentDirectory new) + (setCurrentDirectory orig) + inner From git at git.haskell.org Wed Jul 19 21:17:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:19 +0000 (UTC) Subject: [commit: packages/process] master: Merge branch 'better-travis2' into 74-check-rel-path-subdirs (084070a) Message-ID: <20170719211719.B8CF33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/084070a45973c3dfd3e58d8c0128debea8a839a2/process >--------------------------------------------------------------- commit 084070a45973c3dfd3e58d8c0128debea8a839a2 Merge: 66eaeb6 359a865 Author: Michael Snoyman Date: Sun Nov 13 12:02:21 2016 +0200 Merge branch 'better-travis2' into 74-check-rel-path-subdirs >--------------------------------------------------------------- 084070a45973c3dfd3e58d8c0128debea8a839a2 .travis.yml | 238 ++++++++++++++++++++++++++++++++++++++++++------------------ 1 file changed, 167 insertions(+), 71 deletions(-) From git at git.haskell.org Wed Jul 19 21:17:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:21 +0000 (UTC) Subject: [commit: packages/process] master: Merge branch 'master' of https://github.com/elaforge/process into 74-check-rel-path-subdirs (d636ba2) Message-ID: <20170719211721.C11663A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d636ba2fd36fb371dca70d6b269871053e2ce94f/process >--------------------------------------------------------------- commit d636ba2fd36fb371dca70d6b269871053e2ce94f Merge: 084070a 7c63c9f Author: Michael Snoyman Date: Sun Nov 13 12:07:58 2016 +0200 Merge branch 'master' of https://github.com/elaforge/process into 74-check-rel-path-subdirs >--------------------------------------------------------------- d636ba2fd36fb371dca70d6b269871053e2ce94f System/Process/Common.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) From git at git.haskell.org Wed Jul 19 21:17:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:23 +0000 (UTC) Subject: [commit: packages/process] master: Update changelog (c3cc8fb) Message-ID: <20170719211723.C75FC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c3cc8fb2cf7fbefbdbc10b58f4ff634acd8459bc/process >--------------------------------------------------------------- commit c3cc8fb2cf7fbefbdbc10b58f4ff634acd8459bc Author: Michael Snoyman Date: Sun Nov 13 12:09:40 2016 +0200 Update changelog >--------------------------------------------------------------- c3cc8fb2cf7fbefbdbc10b58f4ff634acd8459bc changelog.md | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index fc27e26..ea07cf8 100644 --- a/changelog.md +++ b/changelog.md @@ -2,7 +2,8 @@ ## Unreleased - * New exposed `withCreateProcess` +* New exposed `withCreateProcess` +* Derive `Show` and `Eq` for `CreateProcess`, `CmdSpec`, and `StdStream` ## 1.4.2.0 *January 2016* From git at git.haskell.org Wed Jul 19 21:17:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:25 +0000 (UTC) Subject: [commit: packages/process] master: Derive Show and Eq for CGid as well (a18ba75) Message-ID: <20170719211725.CDC7A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a18ba7505fd12306d839360798d35af07fd709f7/process >--------------------------------------------------------------- commit a18ba7505fd12306d839360798d35af07fd709f7 Author: Michael Snoyman Date: Sun Nov 13 12:13:39 2016 +0200 Derive Show and Eq for CGid as well >--------------------------------------------------------------- a18ba7505fd12306d839360798d35af07fd709f7 System/Process/Common.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/System/Process/Common.hs b/System/Process/Common.hs index c5e4f57..4b18eb8 100644 --- a/System/Process/Common.hs +++ b/System/Process/Common.hs @@ -57,6 +57,7 @@ import System.Posix.Types -- will never actually be used, as the setuid/setgid system calls are not -- applicable on Windows. No value of this type will ever exist. newtype CGid = CGid Word32 + deriving (Show, Eq) type GroupID = CGid type UserID = CGid #else From git at git.haskell.org Wed Jul 19 21:17:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:27 +0000 (UTC) Subject: [commit: packages/process] master: Comment out lts-2 (c1f80e2) Message-ID: <20170719211727.D440D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c1f80e25121bad1d7ac31a3ab8f8b71ab2435dec/process >--------------------------------------------------------------- commit c1f80e25121bad1d7ac31a3ab8f8b71ab2435dec Author: Michael Snoyman Date: Sun Nov 13 13:57:13 2016 +0200 Comment out lts-2 >--------------------------------------------------------------- c1f80e25121bad1d7ac31a3ab8f8b71ab2435dec .travis.yml | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/.travis.yml b/.travis.yml index e3c680e..c045791 100644 --- a/.travis.yml +++ b/.travis.yml @@ -69,9 +69,11 @@ matrix: compiler: ": #stack default" addons: {apt: {packages: [libgmp-dev]}} - - env: BUILD=stack ARGS="--resolver lts-2" - compiler: ": #stack 7.8.4" - addons: {apt: {packages: [libgmp-dev]}} + # Caused trouble: https://travis-ci.org/haskell/process/jobs/175453678 + # It's OK, covered by cabal build above + #- env: BUILD=stack ARGS="--resolver lts-2" + # compiler: ": #stack 7.8.4" + # addons: {apt: {packages: [libgmp-dev]}} - env: BUILD=stack ARGS="--resolver lts-3" compiler: ": #stack 7.10.2" From git at git.haskell.org Wed Jul 19 21:17:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:29 +0000 (UTC) Subject: [commit: packages/process] master: Slightly more robust tests (55b61d6) Message-ID: <20170719211729.DAA0B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/55b61d6f60822fa68b659de04c360ce0d1b41186/process >--------------------------------------------------------------- commit 55b61d6f60822fa68b659de04c360ce0d1b41186 Author: Michael Snoyman Date: Sun Nov 13 14:17:25 2016 +0200 Slightly more robust tests Signed-off-by: Michael Snoyman >--------------------------------------------------------------- 55b61d6f60822fa68b659de04c360ce0d1b41186 test/main.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/test/main.hs b/test/main.hs index 3bc6d8c..9ea0524 100644 --- a/test/main.hs +++ b/test/main.hs @@ -38,11 +38,11 @@ main = do withCurrentDirectory "exes" $ do res1 <- readCreateProcess (proc "./echo.bat" []) "" - unless ("parent" `isInfixOf` res1) $ error $ + unless ("parent" `isInfixOf` res1 && not ("child" `isInfixOf` res1)) $ error $ "echo.bat with cwd failed: " ++ show res1 res2 <- readCreateProcess (proc "./echo.bat" []) { cwd = Just "subdir" } "" - unless ("child" `isInfixOf` res2) $ error $ + unless ("child" `isInfixOf` res2 && not ("parent" `isInfixOf` res2)) $ error $ "echo.bat with cwd failed: " ++ show res2 putStrLn "Binary handles" From git at git.haskell.org Wed Jul 19 21:17:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:31 +0000 (UTC) Subject: [commit: packages/process] master: Bump upper bound on base (17e0744) Message-ID: <20170719211731.E12063A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/17e07445373ac745f5e47a41b10722742f2f7c41/process >--------------------------------------------------------------- commit 17e07445373ac745f5e47a41b10722742f2f7c41 Author: Ben Gamari Date: Tue Nov 15 12:53:37 2016 -0500 Bump upper bound on base >--------------------------------------------------------------- 17e07445373ac745f5e47a41b10722742f2f7c41 process.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/process.cabal b/process.cabal index 15f6a65..230c017 100644 --- a/process.cabal +++ b/process.cabal @@ -66,7 +66,7 @@ library ghc-options: -Wall - build-depends: base >= 4.4 && < 4.10, + build-depends: base >= 4.4 && < 4.11, directory >= 1.1 && < 1.3, filepath >= 1.2 && < 1.5, deepseq >= 1.1 && < 1.5 From git at git.haskell.org Wed Jul 19 21:17:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:33 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #75 from bgamari/master (24ace49) Message-ID: <20170719211733.E7A383A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/24ace49dc1d564796192310adbbce9ea414f4fe6/process >--------------------------------------------------------------- commit 24ace49dc1d564796192310adbbce9ea414f4fe6 Merge: 55b61d6 17e0744 Author: Michael Snoyman Date: Wed Nov 16 05:23:05 2016 +0200 Merge pull request #75 from bgamari/master Bump upper bound on base >--------------------------------------------------------------- 24ace49dc1d564796192310adbbce9ea414f4fe6 process.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Wed Jul 19 21:17:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:35 +0000 (UTC) Subject: [commit: packages/process] master: Bump directory upper bound to < 1.4 (ede73d3) Message-ID: <20170719211735.EDA013A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ede73d339d0e3333a4ea39e34d7336b17edf563d/process >--------------------------------------------------------------- commit ede73d339d0e3333a4ea39e34d7336b17edf563d Author: Ben Gamari Date: Tue Dec 6 17:20:43 2016 -0500 Bump directory upper bound to < 1.4 >--------------------------------------------------------------- ede73d339d0e3333a4ea39e34d7336b17edf563d process.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/process.cabal b/process.cabal index 07a5a6d..45da92e 100644 --- a/process.cabal +++ b/process.cabal @@ -69,7 +69,7 @@ library ghc-options: -Wall build-depends: base >= 4.4 && < 4.11, - directory >= 1.1 && < 1.3, + directory >= 1.1 && < 1.4, filepath >= 1.2 && < 1.5, deepseq >= 1.1 && < 1.5 From git at git.haskell.org Wed Jul 19 21:17:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:37 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #78 from haskell/bgamari-patch-1 (41cc846) Message-ID: <20170719211737.F3DD43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/41cc84653a75cb14006385fd0412ead4688a1ba2/process >--------------------------------------------------------------- commit 41cc84653a75cb14006385fd0412ead4688a1ba2 Merge: 24ace49 ede73d3 Author: Michael Snoyman Date: Tue Dec 6 18:40:15 2016 -0500 Merge pull request #78 from haskell/bgamari-patch-1 Bump directory upper bound to < 1.4 >--------------------------------------------------------------- 41cc84653a75cb14006385fd0412ead4688a1ba2 process.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Wed Jul 19 21:17:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:40 +0000 (UTC) Subject: [commit: packages/process] master: Version bump for release #79 (28946c6) Message-ID: <20170719211740.063803A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/28946c6ccac40958771aa5541ca64c35be9371fe/process >--------------------------------------------------------------- commit 28946c6ccac40958771aa5541ca64c35be9371fe Author: Michael Snoyman Date: Fri Dec 9 13:53:55 2016 +0200 Version bump for release #79 >--------------------------------------------------------------- 28946c6ccac40958771aa5541ca64c35be9371fe System/Process.hs | 1 + changelog.md | 2 +- process.cabal | 2 +- 3 files changed, 3 insertions(+), 2 deletions(-) diff --git a/System/Process.hs b/System/Process.hs index 3b048b3..aec8786 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -210,6 +210,7 @@ createProcess cp = do -- > withCreateProcess (proc cmd args) { ... } $ \_ _ _ ph -> do -- > ... -- +-- @since 1.4.3.0 -} withCreateProcess :: CreateProcess diff --git a/changelog.md b/changelog.md index ea07cf8..0b274b8 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,6 @@ # Changelog for [`process` package](http://hackage.haskell.org/package/process) -## Unreleased +## 1.4.3.0 *December 2016* * New exposed `withCreateProcess` * Derive `Show` and `Eq` for `CreateProcess`, `CmdSpec`, and `StdStream` diff --git a/process.cabal b/process.cabal index 45da92e..b25c4a2 100644 --- a/process.cabal +++ b/process.cabal @@ -1,5 +1,5 @@ name: process -version: 1.4.2.0 +version: 1.4.3.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE From git at git.haskell.org Wed Jul 19 21:17:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:42 +0000 (UTC) Subject: [commit: packages/process] master: runProcess.c: Clean up whitespace (dc4849d) Message-ID: <20170719211742.0C81D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dc4849dc0fdae1e2f01594cc359d107d0efc1c17/process >--------------------------------------------------------------- commit dc4849dc0fdae1e2f01594cc359d107d0efc1c17 Author: Ben Gamari Date: Mon Dec 12 14:45:08 2016 -0500 runProcess.c: Clean up whitespace >--------------------------------------------------------------- dc4849dc0fdae1e2f01594cc359d107d0efc1c17 cbits/runProcess.c | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/cbits/runProcess.c b/cbits/runProcess.c index 02dea87..fba77a2 100644 --- a/cbits/runProcess.c +++ b/cbits/runProcess.c @@ -240,9 +240,9 @@ runInteractiveProcess (char *const args[], } // XXX Not the pipe for (i = 3; i < max_fd; i++) { - if (i != forkCommunicationFds[1]) { - close(i); - } + if (i != forkCommunicationFds[1]) { + close(i); + } } } From git at git.haskell.org Wed Jul 19 21:17:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:44 +0000 (UTC) Subject: [commit: packages/process] master: runProcess.c: Don't close already closed pipes (9d68cb1) Message-ID: <20170719211744.125BB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9d68cb1bf76d745d1ed9f964f8c6e6397eae4fd6/process >--------------------------------------------------------------- commit 9d68cb1bf76d745d1ed9f964f8c6e6397eae4fd6 Author: Ben Gamari Date: Mon Dec 12 14:45:40 2016 -0500 runProcess.c: Don't close already closed pipes a9a8e914e114913f5eea07da607b29c137bf2041 added some `close` calls which attempted to close pipes that we already closed previously. This resulted in the error code we read from the failed child being overwritten, resulting in the `process004` test failing. >--------------------------------------------------------------- 9d68cb1bf76d745d1ed9f964f8c6e6397eae4fd6 cbits/runProcess.c | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/cbits/runProcess.c b/cbits/runProcess.c index fba77a2..d6eae4a 100644 --- a/cbits/runProcess.c +++ b/cbits/runProcess.c @@ -341,16 +341,16 @@ runInteractiveProcess (char *const args[], waitpid(pid, NULL, 0); if (fdStdIn == -1) { - close(fdStdInput[0]); + // Already closed fdStdInput[0] above close(fdStdInput[1]); } if (fdStdOut == -1) { close(fdStdOutput[0]); - close(fdStdOutput[1]); + // Already closed fdStdOutput[1] above } if (fdStdErr == -1) { close(fdStdError[0]); - close(fdStdError[1]); + // Already closed fdStdError[1] above } pid = -1; From git at git.haskell.org Wed Jul 19 21:17:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:46 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #81 from bgamari/master (a71d831) Message-ID: <20170719211746.1856F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a71d8311e1212758b34aec9449181689ca6bd733/process >--------------------------------------------------------------- commit a71d8311e1212758b34aec9449181689ca6bd733 Merge: 28946c6 9d68cb1 Author: Michael Snoyman Date: Tue Dec 13 14:15:56 2016 +0200 Merge pull request #81 from bgamari/master Don't close already closed pipes >--------------------------------------------------------------- a71d8311e1212758b34aec9449181689ca6bd733 cbits/runProcess.c | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) From git at git.haskell.org Wed Jul 19 21:17:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:48 +0000 (UTC) Subject: [commit: packages/process] master: Update changelog for #81 (85cc1d1) Message-ID: <20170719211748.1E7DA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/85cc1d17e9550a075003a764a2429d4acde65159/process >--------------------------------------------------------------- commit 85cc1d17e9550a075003a764a2429d4acde65159 Author: Michael Snoyman Date: Tue Dec 13 14:17:40 2016 +0200 Update changelog for #81 >--------------------------------------------------------------- 85cc1d17e9550a075003a764a2429d4acde65159 changelog.md | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/changelog.md b/changelog.md index 0b274b8..9f3d755 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,10 @@ # Changelog for [`process` package](http://hackage.haskell.org/package/process) +## Unreleased changes + +* Bug fix: Don't close already closed pipes + [#81](https://github.com/haskell/process/pull/81) + ## 1.4.3.0 *December 2016* * New exposed `withCreateProcess` From git at git.haskell.org Wed Jul 19 21:17:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:50 +0000 (UTC) Subject: [commit: packages/process] master: Relax version bounds. (2307944) Message-ID: <20170719211750.24E093A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2307944517f7a2fe01cad4af6fd8eb761da5f6a2/process >--------------------------------------------------------------- commit 2307944517f7a2fe01cad4af6fd8eb761da5f6a2 Author: Tamar Christina Date: Fri Jan 20 19:54:12 2017 +0000 Relax version bounds. >--------------------------------------------------------------- 2307944517f7a2fe01cad4af6fd8eb761da5f6a2 changelog.md | 1 + process.cabal | 2 +- 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index 9f3d755..73c1814 100644 --- a/changelog.md +++ b/changelog.md @@ -4,6 +4,7 @@ * Bug fix: Don't close already closed pipes [#81](https://github.com/haskell/process/pull/81) +* Relax version bounds of Win32 to allow 2.5. ## 1.4.3.0 *December 2016* diff --git a/process.cabal b/process.cabal index b25c4a2..6734c25 100644 --- a/process.cabal +++ b/process.cabal @@ -50,7 +50,7 @@ library other-modules: System.Process.Common if os(windows) other-modules: System.Process.Windows - build-depends: Win32 >=2.2 && < 2.4 + build-depends: Win32 >=2.2 && < 2.6 extra-libraries: kernel32 cpp-options: -DWINDOWS else From git at git.haskell.org Wed Jul 19 21:17:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:52 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #85 from Mistuke/bump-win32 (6d75056) Message-ID: <20170719211752.2ADBE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6d750563d424c83a9f56a1b4e35c1b6bc007d831/process >--------------------------------------------------------------- commit 6d750563d424c83a9f56a1b4e35c1b6bc007d831 Merge: 85cc1d1 2307944 Author: Michael Snoyman Date: Sun Jan 22 10:33:27 2017 +0200 Merge pull request #85 from Mistuke/bump-win32 Relax Win32 version bounds. >--------------------------------------------------------------- 6d750563d424c83a9f56a1b4e35c1b6bc007d831 changelog.md | 1 + process.cabal | 2 +- 2 files changed, 2 insertions(+), 1 deletion(-) From git at git.haskell.org Wed Jul 19 21:17:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:56 +0000 (UTC) Subject: [commit: packages/process] master: #82, note that all created handles are in text mode. (f044a18) Message-ID: <20170719211756.381003A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f044a18aea16a46411b2639befdd1a9f6f7c4aaf/process >--------------------------------------------------------------- commit f044a18aea16a46411b2639befdd1a9f6f7c4aaf Author: Neil Mitchell Date: Sun Jan 22 15:39:57 2017 +0000 #82, note that all created handles are in text mode. >--------------------------------------------------------------- f044a18aea16a46411b2639befdd1a9f6f7c4aaf System/Process.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/System/Process.hs b/System/Process.hs index 1276f9a..0fc3445 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -178,7 +178,8 @@ Note that @Handle at s provided for @std_in@, @std_out@, or @std_err@ via the @UseHandle@ constructor will be closed by calling this function. This is not always the desired behavior. In cases where you would like to leave the @Handle@ open after spawning the child process, please use 'createProcess_' -instead. +instead. All created @Handle at s are initially in text mode; if you need them +to be in binary mode then use 'hSetBinaryMode'. -} createProcess From git at git.haskell.org Wed Jul 19 21:17:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:54 +0000 (UTC) Subject: [commit: packages/process] master: #82, remove the incorrect notes that Handle's are in binary mode. (77df92f) Message-ID: <20170719211754.3138C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/77df92f15db270a557cad6f3105fd09e3ddb6d97/process >--------------------------------------------------------------- commit 77df92f15db270a557cad6f3105fd09e3ddb6d97 Author: Neil Mitchell Date: Sun Jan 22 15:39:25 2017 +0000 #82, remove the incorrect notes that Handle's are in binary mode. >--------------------------------------------------------------- 77df92f15db270a557cad6f3105fd09e3ddb6d97 System/Process.hs | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/System/Process.hs b/System/Process.hs index aec8786..1276f9a 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -774,8 +774,7 @@ runProcess cmd args mb_cwd mb_env mb_stdin mb_stdout mb_stderr = do {- | Runs a command using the shell, and returns 'Handle's that may be used to communicate with the process via its @stdin@, @stdout@, - and @stderr@ respectively. The 'Handle's are initially in binary - mode; if you need them to be in text mode then use 'hSetBinaryMode'. + and @stderr@ respectively. -} runInteractiveCommand :: String @@ -797,9 +796,6 @@ runInteractiveCommand string = > (inp,out,err,pid) <- runInteractiveProcess "..." > forkIO (hPutStr inp str) - - The 'Handle's are initially in binary mode; if you need them to be - in text mode then use 'hSetBinaryMode'. -} runInteractiveProcess :: FilePath -- ^ Filename of the executable (see 'RawCommand' for details) From git at git.haskell.org Wed Jul 19 21:17:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:17:58 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #86 from ndmitchell/master (0524859) Message-ID: <20170719211758.4002D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0524859137fc01bdb2a4833fd0aa6b23a48c6b15/process >--------------------------------------------------------------- commit 0524859137fc01bdb2a4833fd0aa6b23a48c6b15 Merge: 6d75056 f044a18 Author: Michael Snoyman Date: Sun Jan 22 17:50:06 2017 +0200 Merge pull request #86 from ndmitchell/master Clarify Binary properties of the streams >--------------------------------------------------------------- 0524859137fc01bdb2a4833fd0aa6b23a48c6b15 System/Process.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) From git at git.haskell.org Wed Jul 19 21:18:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:00 +0000 (UTC) Subject: [commit: packages/process] master: GH77: Fix tests (86b273c) Message-ID: <20170719211800.457433A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/86b273c670b78ed1913e9cc2b9a70641b0289f9c/process >--------------------------------------------------------------- commit 86b273c670b78ed1913e9cc2b9a70641b0289f9c Author: Tamar Christina Date: Sun Dec 4 18:45:26 2016 +0000 GH77: Fix tests >--------------------------------------------------------------- 86b273c670b78ed1913e9cc2b9a70641b0289f9c System/Process/Internals.hs | 0 System/Process/Windows.hsc | 0 cbits/runProcess.c | 8 +++++--- 3 files changed, 5 insertions(+), 3 deletions(-) diff --git a/cbits/runProcess.c b/cbits/runProcess.c index b60bf07..6e6fcc1 100644 --- a/cbits/runProcess.c +++ b/cbits/runProcess.c @@ -671,6 +671,7 @@ runInteractiveProcess (wchar_t *cmd, wchar_t *workingDirectory, // the thread suspended. if (useJobObject) { + printf("** NO CALL\n"); dwFlags |= CREATE_SUSPENDED; *hJob = createJob(); if (!*hJob) @@ -684,8 +685,9 @@ runInteractiveProcess (wchar_t *cmd, wchar_t *workingDirectory, goto cleanup_err; } - if (hJob) + if (useJobObject && hJob) { + printf("** NO CALL\n"); // Create the completion port and attach it to the job *hIOcpPort = createCompletionPort (*hJob); if (!*hIOcpPort) @@ -724,8 +726,8 @@ cleanup_err: if (hStdOutputWrite != INVALID_HANDLE_VALUE) CloseHandle(hStdOutputWrite); if (hStdErrorRead != INVALID_HANDLE_VALUE) CloseHandle(hStdErrorRead); if (hStdErrorWrite != INVALID_HANDLE_VALUE) CloseHandle(hStdErrorWrite); - if (hJob ) CloseHandle(hJob); - if (hIOcpPort ) CloseHandle(hIOcpPort); + if (useJobObject && hJob && *hJob ) CloseHandle(*hJob); + if (useJobObject && hIOcpPort && *hIOcpPort) CloseHandle(*hIOcpPort); maperrno(); return NULL; } From git at git.haskell.org Wed Jul 19 21:18:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:02 +0000 (UTC) Subject: [commit: packages/process] master: GH77: fix pattern matching posix. (ad967f8) Message-ID: <20170719211802.4B78D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ad967f819ad001ce54f6ef367165f4b8c143fbb4/process >--------------------------------------------------------------- commit ad967f819ad001ce54f6ef367165f4b8c143fbb4 Author: Tamar Christina Date: Sun Jan 8 09:51:18 2017 +0000 GH77: fix pattern matching posix. >--------------------------------------------------------------- ad967f819ad001ce54f6ef367165f4b8c143fbb4 System/Process/Posix.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/System/Process/Posix.hs b/System/Process/Posix.hs index dbcd285..cd8573f 100644 --- a/System/Process/Posix.hs +++ b/System/Process/Posix.hs @@ -295,7 +295,8 @@ interruptProcessGroupOfInternal interruptProcessGroupOfInternal ph = do withProcessHandle ph $ \p_ -> do case p_ of - ClosedHandle _ -> return () - OpenHandle h -> do + OpenExtHandle{} -> return () + ClosedHandle _ -> return () + OpenHandle h -> do pgid <- getProcessGroupIDOf h signalProcessGroup sigINT pgid From git at git.haskell.org Wed Jul 19 21:18:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:04 +0000 (UTC) Subject: [commit: packages/process] master: GH77: Update testsuite. (e89d6e1) Message-ID: <20170719211804.53D5A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e89d6e1362e77c8d2da57d991327d99b6b51b06a/process >--------------------------------------------------------------- commit e89d6e1362e77c8d2da57d991327d99b6b51b06a Author: Tamar Christina Date: Sat Dec 10 21:56:58 2016 +0000 GH77: Update testsuite. >--------------------------------------------------------------- e89d6e1362e77c8d2da57d991327d99b6b51b06a tests/T9775/T9775_fail.hs | 1 - tests/T9775/T9775_good.hs | 1 - tests/T9775/all.T | 6 ++++++ 3 files changed, 6 insertions(+), 2 deletions(-) diff --git a/tests/T9775/T9775_fail.hs b/tests/T9775/T9775_fail.hs index b9095b1..a3e239e 100644 --- a/tests/T9775/T9775_fail.hs +++ b/tests/T9775/T9775_fail.hs @@ -5,4 +5,3 @@ import System.Process main = do (_,_,_,p) <- createProcess_ "T9775_fail" (proc "main" []) waitForProcess p >>= print - \ No newline at end of file diff --git a/tests/T9775/T9775_good.hs b/tests/T9775/T9775_good.hs index 07600e5..9461754 100644 --- a/tests/T9775/T9775_good.hs +++ b/tests/T9775/T9775_good.hs @@ -9,4 +9,3 @@ main maybe (ExitFailure (-1)) mkExitCode <$> waitForJobCompletion j io timeout_Infinite >>= print where mkExitCode code | code == 0 = ExitSuccess | otherwise = ExitFailure $ fromIntegral code - \ No newline at end of file diff --git a/tests/T9775/all.T b/tests/T9775/all.T index dbccb29..f8d7764 100644 --- a/tests/T9775/all.T +++ b/tests/T9775/all.T @@ -4,3 +4,9 @@ test('T12725_fail', [unless(opsys('mingw32'),skip)] pre_cmd('$MAKE -s --no-print-directory T12725')], compile_and_run, ['']) + +test('T12725_good', + [extra_clean(['ok.o', 'ok.exe', 'main.o', 'main.exe']), + [unless(opsys('mingw32'),skip)] + pre_cmd('$MAKE -s --no-print-directory T12725')], + compile_and_run, ['']) From git at git.haskell.org Wed Jul 19 21:18:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:06 +0000 (UTC) Subject: [commit: packages/process] master: GH77: fix compile errors. (ae57e8c) Message-ID: <20170719211806.59C643A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ae57e8c22b4e7f8356b1f21744add5b2f4d462b1/process >--------------------------------------------------------------- commit ae57e8c22b4e7f8356b1f21744add5b2f4d462b1 Author: Tamar Christina Date: Mon Jan 2 20:30:50 2017 +0000 GH77: fix compile errors. >--------------------------------------------------------------- ae57e8c22b4e7f8356b1f21744add5b2f4d462b1 System/Process/Windows.hsc | 29 +++++++++++++++++++++++++---- cbits/runProcess.c | 15 ++++++++++++--- include/runProcess.h | 5 ++++- tests/T9775/T9775_good.hs | 8 ++------ 4 files changed, 43 insertions(+), 14 deletions(-) diff --git a/System/Process/Windows.hsc b/System/Process/Windows.hsc index b9c4eae..ff8d3a7 100644 --- a/System/Process/Windows.hsc +++ b/System/Process/Windows.hsc @@ -22,6 +22,7 @@ import System.Process.Common import Control.Concurrent import Control.Exception import Data.Bits +import Data.Maybe import Foreign.C import Foreign.Marshal import Foreign.Ptr @@ -197,14 +198,32 @@ waitForJobCompletion :: PHANDLE -> CUInt -> IO (Maybe CInt) waitForJobCompletion job io timeout = - alloca $ \p_exitCode -> do ret <- c_waitForJobCompletion job io timeout p_exitCode - if ret == 0 - then Just <$> peek p_exitCode - else return Nothing + alloca $ \p_exitCode -> do + items <- newMVar $ [] + setter <- mkSetter (insertItem items) + getter <- mkGetter (getItem items) + ret <- c_waitForJobCompletion job io timeout p_exitCode setter getter + if ret == 0 + then Just <$> peek p_exitCode + else return Nothing + +insertItem :: Eq k => MVar [(k, v)] -> k -> v -> IO () +insertItem env_ k v = modifyMVar_ env_ (return . ((k, v):)) + +getItem :: Eq k => MVar [(k, v)] -> k -> IO v +getItem env_ k = withMVar env_ (\m -> return $ fromJust $ lookup k m) -- ---------------------------------------------------------------------------- -- Interface to C bits +type SetterDef = CUInt -> Ptr () -> IO () +type GetterDef = CUInt -> IO (Ptr ()) + +foreign import ccall "wrapper" + mkSetter :: SetterDef -> IO (FunPtr SetterDef) +foreign import ccall "wrapper" + mkGetter :: GetterDef -> IO (FunPtr GetterDef) + foreign import WINDOWS_CCONV unsafe "TerminateJobObject" c_terminateJobObject :: PHANDLE @@ -217,6 +236,8 @@ foreign import ccall interruptible "waitForJobCompletion" -- NB. safe - can bloc -> PHANDLE -> CUInt -> Ptr CInt + -> FunPtr (SetterDef) + -> FunPtr (GetterDef) -> IO CInt foreign import ccall unsafe "runInteractiveProcess" diff --git a/cbits/runProcess.c b/cbits/runProcess.c index 43e3d7a..17463d6 100644 --- a/cbits/runProcess.c +++ b/cbits/runProcess.c @@ -792,8 +792,9 @@ waitForProcess (ProcHandle handle, int *pret) return -1; } + int -waitForJobCompletion (HANDLE hJob, HANDLE ioPort, DWORD timeout, int *pExitCode) +waitForJobCompletion ( HANDLE hJob, HANDLE ioPort, DWORD timeout, int *pExitCode, setterDef set, getterDef get ) { DWORD CompletionCode; ULONG_PTR CompletionKey; @@ -813,15 +814,23 @@ waitForJobCompletion (HANDLE hJob, HANDLE ioPort, DWORD timeout, int *pExitCode) switch (CompletionCode) { case JOB_OBJECT_MSG_NEW_PROCESS: + { // A new child process is born. - break; + // Retrieve and save the process handle from the process id. + // We'll need it for later but we can't retrieve it after the + // process has exited. + DWORD pid = (DWORD)(uintptr_t)Overlapped; + HANDLE pHwnd = OpenProcess(PROCESS_QUERY_LIMITED_INFORMATION, TRUE, pid); + set(pid, pHwnd); + } + break; case JOB_OBJECT_MSG_ABNORMAL_EXIT_PROCESS: case JOB_OBJECT_MSG_EXIT_PROCESS: { // A child process has just exited. // Read exit code, We assume the last process to exit // is the process whose exit code we're interested in. - HANDLE pHwnd = OpenProcess(PROCESS_QUERY_LIMITED_INFORMATION, TRUE, (DWORD)(uintptr_t)Overlapped); + HANDLE pHwnd = get((DWORD)(uintptr_t)Overlapped); if (GetExitCodeProcess(pHwnd, (DWORD *)pExitCode) == 0) { maperrno(); diff --git a/include/runProcess.h b/include/runProcess.h index 1662a62..3807389 100644 --- a/include/runProcess.h +++ b/include/runProcess.h @@ -85,8 +85,11 @@ extern ProcHandle runInteractiveProcess( wchar_t *cmd, HANDLE *hJob, HANDLE *hIOcpPort ); +typedef void(*setterDef)(DWORD, HANDLE); +typedef HANDLE(*getterDef)(DWORD); + extern int terminateJob( ProcHandle handle ); -extern int waitForJobCompletion( HANDLE hJob, HANDLE ioPort, DWORD timeout, int *pExitCode ); +extern int waitForJobCompletion( HANDLE hJob, HANDLE ioPort, DWORD timeout, int *pExitCode, setterDef set, getterDef get ); #endif diff --git a/tests/T9775/T9775_good.hs b/tests/T9775/T9775_good.hs index 9461754..6634ad3 100644 --- a/tests/T9775/T9775_good.hs +++ b/tests/T9775/T9775_good.hs @@ -1,11 +1,7 @@ module Main where import System.Process -import System.Process.Internals -import System.Exit main - = do (_,_,_,_,Just j,Just io) <- createProcessExt_ "T9775_good" True (proc "main" []) - maybe (ExitFailure (-1)) mkExitCode <$> waitForJobCompletion j io timeout_Infinite >>= print - where mkExitCode code | code == 0 = ExitSuccess - | otherwise = ExitFailure $ fromIntegral code + = do (_,_,_,p) <- createProcess_ "T9775_good" (proc "main" []{ use_process_jobs = True }) + waitForProcess p >>= print From git at git.haskell.org Wed Jul 19 21:18:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:08 +0000 (UTC) Subject: [commit: packages/process] master: GH77: Add terminate job (d71248a) Message-ID: <20170719211808.606B63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d71248a3c94d28a4c52d59172c0a18385ccab3f8/process >--------------------------------------------------------------- commit d71248a3c94d28a4c52d59172c0a18385ccab3f8 Author: Tamar Christina Date: Sun Dec 4 10:44:19 2016 +0000 GH77: Add terminate job >--------------------------------------------------------------- d71248a3c94d28a4c52d59172c0a18385ccab3f8 System/Process/Windows.hsc | 51 +++++++++++++++++++++++++++++++++++----------- 1 file changed, 39 insertions(+), 12 deletions(-) diff --git a/System/Process/Windows.hsc b/System/Process/Windows.hsc index c1294fa..5fc07dd 100644 --- a/System/Process/Windows.hsc +++ b/System/Process/Windows.hsc @@ -14,6 +14,8 @@ module System.Process.Windows , createPipeInternal , createPipeInternalFd , interruptProcessGroupOfInternal + , terminateJob + , waitForJobCompletion ) where import System.Process.Common @@ -44,6 +46,14 @@ import System.Win32.Process (getProcessId) #include /* for _O_BINARY */ +##if defined(i386_HOST_ARCH) +## define WINDOWS_CCONV stdcall +##elif defined(x86_64_HOST_ARCH) +## define WINDOWS_CCONV ccall +##else +## error Unknown mingw32 arch +##endif + throwErrnoIfBadPHandle :: String -> IO PHANDLE -> IO PHANDLE throwErrnoIfBadPHandle = throwErrnoIfNull @@ -72,15 +82,7 @@ processHandleFinaliser m = closePHANDLE :: PHANDLE -> IO () closePHANDLE ph = c_CloseHandle ph -foreign import -#if defined(i386_HOST_ARCH) - stdcall -#elif defined(x86_64_HOST_ARCH) - ccall -#else -#error "Unknown architecture" -#endif - unsafe "CloseHandle" +foreign import WINDOWS_CCONV unsafe "CloseHandle" c_CloseHandle :: PHANDLE -> IO () @@ -183,13 +185,38 @@ stopDelegateControlC = return () -- End no-op functions + +-- ---------------------------------------------------------------------------- +-- Interface to C I/O CP bits + +terminateJob :: ProcessHandle -> CUInt -> IO Bool +terminateJob jh ecode = + withProcessHandle jh $ \p_ -> do + case p_ of + ClosedHandle _ -> return False + OpenHandle h -> c_terminateJobObject h ecode + +waitForJobCompletion :: ProcessHandle + -> ProcessHandle + -> CInt + -> IO (Maybe CInt) +waitForJobCompletion jh ioh timeout = + withProcessHandle jh $ \p_ -> + withProcessHandle ioh $ \io_ -> + case (p_, io_) of + (OpenHandle job, OpenHandle io) -> + alloca $ \p_exitCode -> Just <$> + c_waitForJobCompletion job io timeout p_exitCode + _ -> return Nothing + -- ---------------------------------------------------------------------------- -- Interface to C bits -foreign import ccall unsafe "terminateJob" - c_terminateJob +foreign import WINDOWS_CCONV unsafe "TerminateJobObject" + c_terminateJobObject :: PHANDLE - -> IO CInt + -> CUInt + -> IO Bool foreign import ccall interruptible "waitForJobCompletion" -- NB. safe - can block c_waitForJobCompletion From git at git.haskell.org Wed Jul 19 21:18:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:10 +0000 (UTC) Subject: [commit: packages/process] master: GH77: Add appropriate ifdefs. (4a423ad) Message-ID: <20170719211810.66C513A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4a423ad28582d7e0a68b184f6c5eed8a25fa29ef/process >--------------------------------------------------------------- commit 4a423ad28582d7e0a68b184f6c5eed8a25fa29ef Author: Tamar Christina Date: Sun Jan 8 11:29:18 2017 +0000 GH77: Add appropriate ifdefs. >--------------------------------------------------------------- 4a423ad28582d7e0a68b184f6c5eed8a25fa29ef System/Process.hs | 11 +++++++++-- 1 file changed, 9 insertions(+), 2 deletions(-) diff --git a/System/Process.hs b/System/Process.hs index 245ad8b..a0574e4 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -609,10 +609,13 @@ waitForProcess ph@(ProcessHandle _ delegating_ctlc) = do endDelegateControlC e return e OpenExtHandle _ job iocp -> do - maybe (ExitFailure (-1)) mkExitCode <$> waitForJobCompletion job iocp timeout_Infinite +#if defined(WINDOWS) + maybe (ExitFailure (-1)) mkExitCode `fmap` waitForJobCompletion job iocp timeout_Infinite where mkExitCode code | code == 0 = ExitSuccess | otherwise = ExitFailure $ fromIntegral code - +#else + error "OpenExtHandle should not happen on POSIX." +#endif -- ---------------------------------------------------------------------------- -- getProcessExitCode @@ -677,7 +680,11 @@ terminateProcess ph = do withProcessHandle ph $ \p_ -> case p_ of ClosedHandle _ -> return () +#if defined(WINDOWS) OpenExtHandle{} -> terminateJob ph 1 >> return () +#else + OpenExtHandle{} -> error "terminateProcess with OpenExtHandle should not happen on POSIX." +#endif OpenHandle h -> do throwErrnoIfMinus1Retry_ "terminateProcess" $ c_terminateProcess h return () From git at git.haskell.org Wed Jul 19 21:18:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:12 +0000 (UTC) Subject: [commit: packages/process] master: GH77: rebased. (5a12fa4) Message-ID: <20170719211812.6DE5E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5a12fa4a4c19245d7273c2d025223ca3fb619c2b/process >--------------------------------------------------------------- commit 5a12fa4a4c19245d7273c2d025223ca3fb619c2b Author: Tamar Christina Date: Sat Jan 7 15:01:00 2017 +0000 GH77: rebased. >--------------------------------------------------------------- 5a12fa4a4c19245d7273c2d025223ca3fb619c2b cbits/runProcess.c | 2 +- tests/T9775/main.c | 0 tests/T9775/ok.c | 0 3 files changed, 1 insertion(+), 1 deletion(-) diff --git a/cbits/runProcess.c b/cbits/runProcess.c index 17463d6..7ba6a49 100644 --- a/cbits/runProcess.c +++ b/cbits/runProcess.c @@ -518,7 +518,7 @@ createJob () ZeroMemory(&jeli, sizeof(JOBOBJECT_EXTENDED_LIMIT_INFORMATION)); // Configure all child processes associated with the job to terminate when the // Last process in the job terminates. This prevent half dead processes. - //jeli.BasicLimitInformation.LimitFlags = JOB_OBJECT_LIMIT_KILL_ON_JOB_CLOSE; + jeli.BasicLimitInformation.LimitFlags = JOB_OBJECT_LIMIT_KILL_ON_JOB_CLOSE; if (SetInformationJobObject (hJob, JobObjectExtendedLimitInformation, &jeli, sizeof(JOBOBJECT_EXTENDED_LIMIT_INFORMATION))) From git at git.haskell.org Wed Jul 19 21:18:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:14 +0000 (UTC) Subject: [commit: packages/process] master: GH77: fix tests (eb85aac) Message-ID: <20170719211814.7424E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eb85aacbd1f58655ae74c920b1b3208f8ce7ba94/process >--------------------------------------------------------------- commit eb85aacbd1f58655ae74c920b1b3208f8ce7ba94 Author: Tamar Christina Date: Sun Dec 11 12:01:03 2016 +0000 GH77: fix tests >--------------------------------------------------------------- eb85aacbd1f58655ae74c920b1b3208f8ce7ba94 tests/T9775/Makefile | 2 +- tests/T9775/all.T | 10 ++++++---- 2 files changed, 7 insertions(+), 5 deletions(-) diff --git a/tests/T9775/Makefile b/tests/T9775/Makefile index 6eafccf..f5a54bc 100644 --- a/tests/T9775/Makefile +++ b/tests/T9775/Makefile @@ -2,7 +2,7 @@ # assumes the package is part of a GHC build tree with the testsuite # installed in ../../../testsuite. -TOP=../../../testsuite +TOP=../../../../testsuite include $(TOP)/mk/boilerplate.mk include $(TOP)/mk/test.mk diff --git a/tests/T9775/all.T b/tests/T9775/all.T index 694c0c8..55e7750 100644 --- a/tests/T9775/all.T +++ b/tests/T9775/all.T @@ -1,12 +1,14 @@ test('T9775_fail', [extra_clean(['ok.o', 'ok.exe', 'main.o', 'main.exe']), - [unless(opsys('mingw32'),skip)], + extra_files(['ok.c', 'main.c']), + unless(opsys('mingw32'),skip), pre_cmd('$MAKE -s --no-print-directory T9775')], - compile_and_run, ['']) + compile_and_run, ['']) test('T9775_good', [extra_clean(['ok.o', 'ok.exe', 'main.o', 'main.exe']), - [unless(opsys('mingw32'),skip)], + unless(opsys('mingw32'),skip), + extra_files(['ok.c', 'main.c']), pre_cmd('$MAKE -s --no-print-directory T9775')], - compile_and_run, ['']) + compile_and_run, ['']) From git at git.haskell.org Wed Jul 19 21:18:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:16 +0000 (UTC) Subject: [commit: packages/process] master: GH77: restored compatibility. (c3c067b) Message-ID: <20170719211816.7AFC43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c3c067be022d192a7599476afd3bed903070b4a1/process >--------------------------------------------------------------- commit c3c067be022d192a7599476afd3bed903070b4a1 Author: Tamar Christina Date: Sat Jan 7 11:51:44 2017 +0000 GH77: restored compatibility. >--------------------------------------------------------------- c3c067be022d192a7599476afd3bed903070b4a1 System/Process.hs | 34 +++++++++++++++++++++------------- System/Process/Internals.hs | 8 ++++---- process.cabal | 2 +- tests/T9775/T9775_fail.hs | 2 +- tests/T9775/T9775_good.hs | 2 +- 5 files changed, 28 insertions(+), 20 deletions(-) diff --git a/System/Process.hs b/System/Process.hs index f9db2d0..245ad8b 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -192,7 +192,7 @@ createProcess cp = do maybeCloseStd (std_in cp) maybeCloseStd (std_out cp) maybeCloseStd (std_err cp) - return $ unwrapHandles r + return r where maybeCloseStd :: StdStream -> IO () maybeCloseStd (UseHandle hdl) @@ -230,7 +230,7 @@ withCreateProcess_ -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a) -> IO a withCreateProcess_ fun c action = - C.bracketOnError (unwrapHandles <$> createProcess_ fun c) cleanupProcess + C.bracketOnError (createProcess_ fun c) cleanupProcess (\(m_in, m_out, m_err, ph) -> action m_in m_out m_err ph) @@ -269,16 +269,18 @@ cleanupProcess (mb_stdin, mb_stdout, mb_stderr, -- -- @since 1.2.0.0 spawnProcess :: FilePath -> [String] -> IO ProcessHandle -spawnProcess cmd args = - procHandle <$> createProcess_ "spawnProcess" (proc cmd args) +spawnProcess cmd args = do + (_,_,_,p) <- createProcess_ "spawnProcess" (proc cmd args) + return p -- | Creates a new process to run the specified shell command. -- It does not wait for the program to finish, but returns the 'ProcessHandle'. -- -- @since 1.2.0.0 spawnCommand :: String -> IO ProcessHandle -spawnCommand cmd = - procHandle <$> createProcess_ "spawnCommand" (shell cmd) +spawnCommand cmd = do + (_,_,_,p) <- createProcess_ "spawnCommand" (shell cmd) + return p -- ---------------------------------------------------------------------------- @@ -725,8 +727,9 @@ runCommand :: String -> IO ProcessHandle -runCommand string = - procHandle <$> createProcess_ "runCommand" (shell string) +runCommand string = do + (_,_,_,ph) <- createProcess_ "runCommand" (shell string) + return ph -- ---------------------------------------------------------------------------- @@ -756,7 +759,8 @@ runProcess -> IO ProcessHandle runProcess cmd args mb_cwd mb_env mb_stdin mb_stdout mb_stderr = do - r <- createProcess_ "runProcess" + (_,_,_,ph) <- + createProcess_ "runProcess" (proc cmd args){ cwd = mb_cwd, env = mb_env, std_in = mbToStd mb_stdin, @@ -765,7 +769,7 @@ runProcess cmd args mb_cwd mb_env mb_stdin mb_stdout mb_stderr = do maybeClose mb_stdin maybeClose mb_stdout maybeClose mb_stderr - return $ procHandle r + return ph where maybeClose :: Maybe Handle -> IO () maybeClose (Just hdl) @@ -824,7 +828,7 @@ runInteractiveProcess1 -> IO (Handle,Handle,Handle,ProcessHandle) runInteractiveProcess1 fun cmd = do (mb_in, mb_out, mb_err, p) <- - unwrapHandles <$> createProcess_ fun + createProcess_ fun cmd{ std_in = CreatePipe, std_out = CreatePipe, std_err = CreatePipe } @@ -861,7 +865,9 @@ when the process died as the result of a signal. -} system :: String -> IO ExitCode system "" = ioException (ioeSetErrorString (mkIOError InvalidArgument "system" Nothing Nothing) "null command") -system str = procHandle <$> createProcess_ "system" (shell str) { delegate_ctlc = True } >>= waitForProcess +system str = do + (_,_,_,p) <- createProcess_ "system" (shell str) { delegate_ctlc = True } + waitForProcess p --TODO: in a later release {-# DEPRECATED rawSystem "Use 'callProcess' (or 'spawnProcess' and 'waitForProcess') instead" #-} @@ -875,4 +881,6 @@ It will therefore behave more portably between operating systems than 'system'. The return codes and possible failures are the same as for 'system'. -} rawSystem :: String -> [String] -> IO ExitCode -rawSystem cmd args = procHandle <$> createProcess_ "rawSystem" (proc cmd args) { delegate_ctlc = True } >>= waitForProcess +rawSystem cmd args = do + (_,_,_,p) <- createProcess_ "rawSystem" (proc cmd args) { delegate_ctlc = True } + waitForProcess p diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index 99196c9..299f834 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -90,8 +90,8 @@ import System.Process.Posix createProcess_ :: String -- ^ function name (for error messages) -> CreateProcess - -> IO ProcRetHandles -createProcess_ = createProcess_Internal + -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) +createProcess_ msg proc_ = unwrapHandles <$> createProcess_Internal msg proc_ {-# INLINE createProcess_ #-} -- ------------------------------------------------------------------------ @@ -171,8 +171,8 @@ runGenProcess_ -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -- On Windows, setting delegate_ctlc has no impact runGenProcess_ fun c (Just sig) (Just sig') | isDefaultSignal sig && sig == sig' - = unwrapHandles <$> createProcess_ fun c { delegate_ctlc = True } -runGenProcess_ fun c _ _ = unwrapHandles <$> createProcess_ fun c + = createProcess_ fun c { delegate_ctlc = True } +runGenProcess_ fun c _ _ = createProcess_ fun c -- --------------------------------------------------------------------------- -- createPipe diff --git a/process.cabal b/process.cabal index 6734c25..b339938 100644 --- a/process.cabal +++ b/process.cabal @@ -1,5 +1,5 @@ name: process -version: 1.4.3.0 +version: 1.4.3.1 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE diff --git a/tests/T9775/T9775_fail.hs b/tests/T9775/T9775_fail.hs index a3e239e..b2cc020 100644 --- a/tests/T9775/T9775_fail.hs +++ b/tests/T9775/T9775_fail.hs @@ -3,5 +3,5 @@ module Main where import System.Process main - = do (_,_,_,p) <- createProcess_ "T9775_fail" (proc "main" []) + = do (_,_,_,p) <- createProcess (proc "main" []) waitForProcess p >>= print diff --git a/tests/T9775/T9775_good.hs b/tests/T9775/T9775_good.hs index 6634ad3..a66c316 100644 --- a/tests/T9775/T9775_good.hs +++ b/tests/T9775/T9775_good.hs @@ -3,5 +3,5 @@ module Main where import System.Process main - = do (_,_,_,p) <- createProcess_ "T9775_good" (proc "main" []{ use_process_jobs = True }) + = do (_,_,_,p) <- createProcess ((proc "main" []){ use_process_jobs = True }) waitForProcess p >>= print From git at git.haskell.org Wed Jul 19 21:18:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:18 +0000 (UTC) Subject: [commit: packages/process] master: GH77: Added note.' (523b3dd) Message-ID: <20170719211818.819C53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/523b3ddc54e81fdfb7bf1aab32f03e387ca972d1/process >--------------------------------------------------------------- commit 523b3ddc54e81fdfb7bf1aab32f03e387ca972d1 Author: Tamar Christina Date: Tue Jan 17 19:02:39 2017 +0000 GH77: Added note.' >--------------------------------------------------------------- 523b3ddc54e81fdfb7bf1aab32f03e387ca972d1 cbits/runProcess.c | 37 +++++++++++++++++++++++++++++++++++-- 1 file changed, 35 insertions(+), 2 deletions(-) diff --git a/cbits/runProcess.c b/cbits/runProcess.c index d6c26cc..ae184c8 100644 --- a/cbits/runProcess.c +++ b/cbits/runProcess.c @@ -553,6 +553,38 @@ createCompletionPort (HANDLE hJob) return ioPort; } +/* Note [Windows exec interaction] + + The basic issue that process jobs tried to solve is this: + + Say you have two programs A and B. Now A calls B. There are two ways to do this. + + 1) You can use the normal CreateProcess API, which is what normal Windows code do. + Using this approach, the current waitForProcess works absolutely fine. + 2) You can call the emulated POSIX function _exec, which of course is supposed to + allow the child process to replace the parent. + + With approach 2) waitForProcess falls apart because the Win32's process model does + not allow this the same way as linux. _exec is emulated by first making a call to + CreateProcess to spawn B and then immediately exiting from A. So you have two + different processes. + + waitForProcess is waiting on the termination of A. Because A is immediately killed, + waitForProcess will return even though B is still running. This is why for instance + the GHC testsuite on Windows had lots of file locked errors. + + This approach creates a new Job and assigned A to the job, but also all future + processes spawned by A. This allows us to listen in on events, such as, when all + processes in the job are finished, but also allows us to propagate exit codes from + _exec calls. + + The only reason we need this at all is because we don't interact with just actual + native code on Windows, and instead have a lot of ported POSIX code. + + The Job handle is returned to the user because Jobs have additional benefits as well, + such as allowing you to specify resource limits on the to be spawned process. + */ + ProcHandle runInteractiveProcess (wchar_t *cmd, wchar_t *workingDirectory, wchar_t *environment, @@ -668,8 +700,9 @@ runInteractiveProcess (wchar_t *cmd, wchar_t *workingDirectory, dwFlags |= CREATE_NEW_CONSOLE; } - // If we're going to use a job object, then we have to create - // the thread suspended. + /* If we're going to use a job object, then we have to create + the thread suspended. + See Note [Windows exec interaction]. */ if (useJobObject) { dwFlags |= CREATE_SUSPENDED; From git at git.haskell.org Wed Jul 19 21:18:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:20 +0000 (UTC) Subject: [commit: packages/process] master: GH77: Add scaffolding. (684ce18) Message-ID: <20170719211820.88E3B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/684ce185464e28acff2c5938f83274824db052f4/process >--------------------------------------------------------------- commit 684ce185464e28acff2c5938f83274824db052f4 Author: Tamar Christina Date: Sat Dec 3 10:12:08 2016 +0000 GH77: Add scaffolding. >--------------------------------------------------------------- 684ce185464e28acff2c5938f83274824db052f4 System/Process/Windows.hsc | 77 +++++++++++++++++++------ cbits/runProcess.c | 137 ++++++++++++++++++++++++++++++++++++++++++++- include/runProcess.h | 9 ++- 3 files changed, 204 insertions(+), 19 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 684ce185464e28acff2c5938f83274824db052f4 From git at git.haskell.org Wed Jul 19 21:18:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:22 +0000 (UTC) Subject: [commit: packages/process] master: GH77: replace <$> with fmap (2d6933b) Message-ID: <20170719211822.8ED9A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2d6933b5afeb6e8c468b74d25c071e0afb779f38/process >--------------------------------------------------------------- commit 2d6933b5afeb6e8c468b74d25c071e0afb779f38 Author: Tamar Christina Date: Sun Jan 8 09:52:35 2017 +0000 GH77: replace <$> with fmap >--------------------------------------------------------------- 2d6933b5afeb6e8c468b74d25c071e0afb779f38 System/Process/Internals.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index 299f834..026cd99 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -91,7 +91,7 @@ createProcess_ :: String -- ^ function name (for error messages) -> CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -createProcess_ msg proc_ = unwrapHandles <$> createProcess_Internal msg proc_ +createProcess_ msg proc_ = unwrapHandles `fmap` createProcess_Internal msg proc_ {-# INLINE createProcess_ #-} -- ------------------------------------------------------------------------ From git at git.haskell.org Wed Jul 19 21:18:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:24 +0000 (UTC) Subject: [commit: packages/process] master: GH77: Update readme and export list. (57e0c7f) Message-ID: <20170719211824.9600C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/57e0c7f17823ccbc6d5aeacb3425c1d412163102/process >--------------------------------------------------------------- commit 57e0c7f17823ccbc6d5aeacb3425c1d412163102 Author: Tamar Christina Date: Sun Dec 4 16:25:07 2016 +0000 GH77: Update readme and export list. >--------------------------------------------------------------- 57e0c7f17823ccbc6d5aeacb3425c1d412163102 System/Process/Internals.hs | 3 +++ changelog.md | 3 ++- 2 files changed, 5 insertions(+), 1 deletion(-) diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index af42009..fad7c92 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -34,6 +34,9 @@ module System.Process.Internals ( #ifndef WINDOWS pPrPr_disableITimers, c_execvpe, ignoreSignal, defaultSignal, +#else + terminateJob, + waitForJobCompletion, #endif withFilePathException, withCEnvironment, translate, diff --git a/changelog.md b/changelog.md index a8e7738..3fd77f8 100644 --- a/changelog.md +++ b/changelog.md @@ -10,7 +10,8 @@ * New exposed `withCreateProcess` * Derive `Show` and `Eq` for `CreateProcess`, `CmdSpec`, and `StdStream` -* Add support for monitoring process tree for termination with `...` +* Add support for monitoring process tree for termination with `createProcess_Internal_ext` + , `terminateJob` and `waitForJobCompletion`. ## 1.4.2.0 *January 2016* From git at git.haskell.org Wed Jul 19 21:18:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:26 +0000 (UTC) Subject: [commit: packages/process] master: GH77: remove typo. (5a0d7bc) Message-ID: <20170719211826.9C7D53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5a0d7bcdb353e283eea7daaeb0517d2164cb8041/process >--------------------------------------------------------------- commit 5a0d7bcdb353e283eea7daaeb0517d2164cb8041 Author: Tamar Christina Date: Sun Jan 8 06:36:04 2017 +0000 GH77: remove typo. >--------------------------------------------------------------- 5a0d7bcdb353e283eea7daaeb0517d2164cb8041 System/Process/Posix.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Process/Posix.hs b/System/Process/Posix.hs index 201c4e9..dbcd285 100644 --- a/System/Process/Posix.hs +++ b/System/Process/Posix.hs @@ -169,7 +169,7 @@ createProcess_Internal fun return ProcRetHandles { hStdInput = hndStdInput , hStdOutput = hndStdOutput , hStdError = hndStdError - , procHandle = ph] + , procHandle = ph } {-# NOINLINE runInteractiveProcess_lock #-} From git at git.haskell.org Wed Jul 19 21:18:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:30 +0000 (UTC) Subject: [commit: packages/process] master: GH77: Accept output. (605ce3e) Message-ID: <20170719211830.AA7463A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/605ce3e53e0e7672e76a4c890c39bc48d8dca39d/process >--------------------------------------------------------------- commit 605ce3e53e0e7672e76a4c890c39bc48d8dca39d Author: Tamar Christina Date: Sun Dec 11 15:23:19 2016 +0000 GH77: Accept output. >--------------------------------------------------------------- 605ce3e53e0e7672e76a4c890c39bc48d8dca39d tests/{T4889.stdout => T9775/T9775_fail.stdout} | 2 +- tests/T9775/T9775_good.stdout | 2 ++ 2 files changed, 3 insertions(+), 1 deletion(-) diff --git a/tests/T4889.stdout b/tests/T9775/T9775_fail.stdout similarity index 60% copy from tests/T4889.stdout copy to tests/T9775/T9775_fail.stdout index d72cac5..7374c53 100644 --- a/tests/T4889.stdout +++ b/tests/T9775/T9775_fail.stdout @@ -1,2 +1,2 @@ ExitSuccess -1 +bye bye diff --git a/tests/T9775/T9775_good.stdout b/tests/T9775/T9775_good.stdout new file mode 100644 index 0000000..e08b355 --- /dev/null +++ b/tests/T9775/T9775_good.stdout @@ -0,0 +1,2 @@ +bye bye +ExitFailure 120 From git at git.haskell.org Wed Jul 19 21:18:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:28 +0000 (UTC) Subject: [commit: packages/process] master: GH77: Finish implementation. (282aa2e) Message-ID: <20170719211828.A318B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/282aa2e3a4893da8b685d86c8bdb498350010843/process >--------------------------------------------------------------- commit 282aa2e3a4893da8b685d86c8bdb498350010843 Author: Tamar Christina Date: Sat Dec 10 21:35:31 2016 +0000 GH77: Finish implementation. >--------------------------------------------------------------- 282aa2e3a4893da8b685d86c8bdb498350010843 System/Process.hs | 2 +- System/Process/Internals.hs | 1 + System/Process/Windows.hsc | 4 ++++ cbits/runProcess.c | 10 ++++------ tests/T9775/T9775_fail.hs | 0 tests/T9775/T9775_good.hs | 2 +- 6 files changed, 11 insertions(+), 8 deletions(-) diff --git a/System/Process.hs b/System/Process.hs index 44a4362..aa868f4 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -879,7 +879,7 @@ executeAndWait :: String -> CreateProcess -> IO ExitCode executeAndWait name proc_ = do #if defined(WINDOWS) (_,_,_,_,Just job,Just iocp) <- createProcessExt_ name True proc_ - maybe (ExitFailure (-1)) mkExitCode <$> waitForJobCompletion job iocp (-1) + maybe (ExitFailure (-1)) mkExitCode <$> waitForJobCompletion job iocp timeout_Infinite where mkExitCode code | code == 0 = ExitSuccess | otherwise = ExitFailure $ fromIntegral code #else diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index c3dd4bd..29e348d 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -37,6 +37,7 @@ module System.Process.Internals ( #else terminateJob, waitForJobCompletion, + timeout_Infinite, #endif withFilePathException, withCEnvironment, translate, diff --git a/System/Process/Windows.hsc b/System/Process/Windows.hsc index cb40a3e..c28ff07 100644 --- a/System/Process/Windows.hsc +++ b/System/Process/Windows.hsc @@ -16,6 +16,7 @@ module System.Process.Windows , interruptProcessGroupOfInternal , terminateJob , waitForJobCompletion + , timeout_Infinite ) where import System.Process.Common @@ -196,6 +197,9 @@ terminateJob jh ecode = ClosedHandle _ -> return False OpenHandle h -> c_terminateJobObject h ecode +timeout_Infinite :: CUInt +timeout_Infinite = 0xFFFFFFFF + waitForJobCompletion :: ProcessHandle -> ProcessHandle -> CUInt diff --git a/cbits/runProcess.c b/cbits/runProcess.c index cb87dc8..43e3d7a 100644 --- a/cbits/runProcess.c +++ b/cbits/runProcess.c @@ -798,8 +798,7 @@ waitForJobCompletion (HANDLE hJob, HANDLE ioPort, DWORD timeout, int *pExitCode) DWORD CompletionCode; ULONG_PTR CompletionKey; LPOVERLAPPED Overlapped; - *pExitCode = 5; - HANDLE lastProc; + *pExitCode = 0; // We have to loop here. It's a blocking call, but // we get notified on each completion event. So if it's @@ -815,7 +814,6 @@ waitForJobCompletion (HANDLE hJob, HANDLE ioPort, DWORD timeout, int *pExitCode) { case JOB_OBJECT_MSG_NEW_PROCESS: // A new child process is born. - lastProc = OpenProcess(PROCESS_QUERY_LIMITED_INFORMATION, TRUE, (DWORD)(uintptr_t)Overlapped); break; case JOB_OBJECT_MSG_ABNORMAL_EXIT_PROCESS: case JOB_OBJECT_MSG_EXIT_PROCESS: @@ -823,12 +821,12 @@ waitForJobCompletion (HANDLE hJob, HANDLE ioPort, DWORD timeout, int *pExitCode) // A child process has just exited. // Read exit code, We assume the last process to exit // is the process whose exit code we're interested in. - if (GetExitCodeProcess (lastProc, (DWORD *)pExitCode) == 0) + HANDLE pHwnd = OpenProcess(PROCESS_QUERY_LIMITED_INFORMATION, TRUE, (DWORD)(uintptr_t)Overlapped); + if (GetExitCodeProcess(pHwnd, (DWORD *)pExitCode) == 0) { maperrno(); - return -1; + return 1; } - printf("Exit(0x%x): %d\n", (HANDLE)Overlapped, *pExitCode); } break; case JOB_OBJECT_MSG_ACTIVE_PROCESS_ZERO: diff --git a/tests/T9775/T9775_good.hs b/tests/T9775/T9775_good.hs index 48b7376..07600e5 100644 --- a/tests/T9775/T9775_good.hs +++ b/tests/T9775/T9775_good.hs @@ -6,7 +6,7 @@ import System.Exit main = do (_,_,_,_,Just j,Just io) <- createProcessExt_ "T9775_good" True (proc "main" []) - maybe (ExitFailure (-7)) mkExitCode <$> waitForJobCompletion j io 0xFFFFFFFF >>= print + maybe (ExitFailure (-1)) mkExitCode <$> waitForJobCompletion j io timeout_Infinite >>= print where mkExitCode code | code == 0 = ExitSuccess | otherwise = ExitFailure $ fromIntegral code \ No newline at end of file From git at git.haskell.org Wed Jul 19 21:18:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:32 +0000 (UTC) Subject: [commit: packages/process] master: GH77: Update readme. (7ef688e) Message-ID: <20170719211832.B03A53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7ef688e2e716b309ad70926d3ce79791def57e4f/process >--------------------------------------------------------------- commit 7ef688e2e716b309ad70926d3ce79791def57e4f Author: Tamar Christina Date: Thu Jan 5 19:53:40 2017 +0000 GH77: Update readme. >--------------------------------------------------------------- 7ef688e2e716b309ad70926d3ce79791def57e4f changelog.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/changelog.md b/changelog.md index f5ab09a..991be99 100644 --- a/changelog.md +++ b/changelog.md @@ -10,8 +10,8 @@ * New exposed `withCreateProcess` * Derive `Show` and `Eq` for `CreateProcess`, `CmdSpec`, and `StdStream` -* Add support for monitoring process tree for termination with `createProcess_Internal_ext` - , `terminateJob`, `waitForJobCompletion` and a new generic function `executeAndWait`. +* Add support for monitoring process tree for termination with the parameter `use_process_jobs` + in `CreateProcess` on Windows. Also added a function `terminateJob` to kill entire process tree. ## 1.4.2.0 *January 2016* From git at git.haskell.org Wed Jul 19 21:18:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:34 +0000 (UTC) Subject: [commit: packages/process] master: GH77: rewrote implementation. (3a5935c) Message-ID: <20170719211834.B8DB23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3a5935ce6353e5c9e35214a070c31342098e5c6c/process >--------------------------------------------------------------- commit 3a5935ce6353e5c9e35214a070c31342098e5c6c Author: Tamar Christina Date: Mon Jan 2 15:54:07 2017 +0000 GH77: rewrote implementation. >--------------------------------------------------------------- 3a5935ce6353e5c9e35214a070c31342098e5c6c System/Process.hs | 76 ++++++++++++++++++---------------------- System/Process/Common.hs | 25 ++++++++++++-- System/Process/Internals.hs | 57 ++++++++++++------------------ System/Process/Posix.hs | 10 ++++-- System/Process/Windows.hsc | 84 ++++++++++++++++++++------------------------- 5 files changed, 122 insertions(+), 130 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 3a5935ce6353e5c9e35214a070c31342098e5c6c From git at git.haskell.org Wed Jul 19 21:18:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:36 +0000 (UTC) Subject: [commit: packages/process] master: GH77: update tests. (2e3542d) Message-ID: <20170719211836.BF2473A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2e3542d060088d2a518286c498d69ac24b3df77a/process >--------------------------------------------------------------- commit 2e3542d060088d2a518286c498d69ac24b3df77a Author: Tamar Christina Date: Sun Dec 11 00:07:08 2016 +0000 GH77: update tests. >--------------------------------------------------------------- 2e3542d060088d2a518286c498d69ac24b3df77a tests/T9775/Makefile | 4 ++-- tests/T9775/all.T | 12 ++++++------ 2 files changed, 8 insertions(+), 8 deletions(-) diff --git a/tests/T9775/Makefile b/tests/T9775/Makefile index 65191d5..6eafccf 100644 --- a/tests/T9775/Makefile +++ b/tests/T9775/Makefile @@ -6,8 +6,8 @@ TOP=../../../testsuite include $(TOP)/mk/boilerplate.mk include $(TOP)/mk/test.mk -.PHONY: T12725 -T12725: +.PHONY: T9775 +T9775: '$(TEST_CC)' ok.c -o ok.exe '$(TEST_CC)' main.c -o main.exe diff --git a/tests/T9775/all.T b/tests/T9775/all.T index f8d7764..694c0c8 100644 --- a/tests/T9775/all.T +++ b/tests/T9775/all.T @@ -1,12 +1,12 @@ -test('T12725_fail', +test('T9775_fail', [extra_clean(['ok.o', 'ok.exe', 'main.o', 'main.exe']), - [unless(opsys('mingw32'),skip)] - pre_cmd('$MAKE -s --no-print-directory T12725')], + [unless(opsys('mingw32'),skip)], + pre_cmd('$MAKE -s --no-print-directory T9775')], compile_and_run, ['']) -test('T12725_good', +test('T9775_good', [extra_clean(['ok.o', 'ok.exe', 'main.o', 'main.exe']), - [unless(opsys('mingw32'),skip)] - pre_cmd('$MAKE -s --no-print-directory T12725')], + [unless(opsys('mingw32'),skip)], + pre_cmd('$MAKE -s --no-print-directory T9775')], compile_and_run, ['']) From git at git.haskell.org Wed Jul 19 21:18:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:38 +0000 (UTC) Subject: [commit: packages/process] master: GH77: fixed bug. (94a2140) Message-ID: <20170719211838.C53493A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/94a2140511345df3aab8185fa338bbde03421926/process >--------------------------------------------------------------- commit 94a2140511345df3aab8185fa338bbde03421926 Author: Tamar Christina Date: Mon Jan 16 02:39:13 2017 +0000 GH77: fixed bug. >--------------------------------------------------------------- 94a2140511345df3aab8185fa338bbde03421926 cbits/runProcess.c | 3 +++ 1 file changed, 3 insertions(+) diff --git a/cbits/runProcess.c b/cbits/runProcess.c index 7ba6a49..d6c26cc 100644 --- a/cbits/runProcess.c +++ b/cbits/runProcess.c @@ -685,6 +685,9 @@ runInteractiveProcess (wchar_t *cmd, wchar_t *workingDirectory, { goto cleanup_err; } + } else { + *hJob = NULL; + *hIOcpPort = NULL; } if (!CreateProcess(NULL, cmd, NULL, NULL, inherit, dwFlags, environment, workingDirectory, &sInfo, &pInfo)) From git at git.haskell.org Wed Jul 19 21:18:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:40 +0000 (UTC) Subject: [commit: packages/process] master: GH77: fix Posix. (e41616e) Message-ID: <20170719211840.CB1703A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e41616e249ea56de4321d4b9227c985a3522798f/process >--------------------------------------------------------------- commit e41616e249ea56de4321d4b9227c985a3522798f Author: Tamar Christina Date: Sun Jan 8 00:34:19 2017 +0000 GH77: fix Posix. >--------------------------------------------------------------- e41616e249ea56de4321d4b9227c985a3522798f System/Process/Posix.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/System/Process/Posix.hs b/System/Process/Posix.hs index 8b92165..201c4e9 100644 --- a/System/Process/Posix.hs +++ b/System/Process/Posix.hs @@ -169,9 +169,7 @@ createProcess_Internal fun return ProcRetHandles { hStdInput = hndStdInput , hStdOutput = hndStdOutput , hStdError = hndStdError - , procHandle = ph - , procJobHandle = Nothing - , procPortHandle = Nothing + , procHandle = ph] } {-# NOINLINE runInteractiveProcess_lock #-} From git at git.haskell.org Wed Jul 19 21:18:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:44 +0000 (UTC) Subject: [commit: packages/process] master: GH77: Working (3bf217f) Message-ID: <20170719211844.DAF4B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3bf217f1170975205d571a5de3680d9616675319/process >--------------------------------------------------------------- commit 3bf217f1170975205d571a5de3680d9616675319 Author: Tamar Christina Date: Sat Dec 10 20:34:30 2016 +0000 GH77: Working >--------------------------------------------------------------- 3bf217f1170975205d571a5de3680d9616675319 System/Process/Windows.hsc | 18 ++++++++++-------- cbits/runProcess.c | 34 +++++++++++++++++++++------------- tests/T9775/T9775_fail.hs | 4 ++-- tests/T9775/T9775_good.hs | 12 ++++++++++++ tests/T9775/ok.c | 6 ++++-- 5 files changed, 49 insertions(+), 25 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3bf217f1170975205d571a5de3680d9616675319 From git at git.haskell.org Wed Jul 19 21:18:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:42 +0000 (UTC) Subject: [commit: packages/process] master: GH77: Add failing test for Windows. (e7827bb) Message-ID: <20170719211842.D2D6B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e7827bb4858130fbecae9abad04bb6f98e17ad2f/process >--------------------------------------------------------------- commit e7827bb4858130fbecae9abad04bb6f98e17ad2f Author: Tamar Christina Date: Sun Dec 4 20:03:27 2016 +0000 GH77: Add failing test for Windows. >--------------------------------------------------------------- e7827bb4858130fbecae9abad04bb6f98e17ad2f tests/{ => T9775}/Makefile | 7 ++++--- tests/T9775/T9775_fail.hs | 8 ++++++++ tests/T9775/all.T | 6 ++++++ tests/T9775/main.c | 6 ++++++ tests/T9775/ok.c | 6 ++++++ 5 files changed, 30 insertions(+), 3 deletions(-) diff --git a/tests/Makefile b/tests/T9775/Makefile similarity index 65% copy from tests/Makefile copy to tests/T9775/Makefile index 63b3e74..65191d5 100644 --- a/tests/Makefile +++ b/tests/T9775/Makefile @@ -6,7 +6,8 @@ TOP=../../../testsuite include $(TOP)/mk/boilerplate.mk include $(TOP)/mk/test.mk -.PHONY: process007_fd -process007_fd: - '$(TEST_HC)' -optc='-Wall' -no-hs-main -no-auto-link-packages process007_fd.c -o process007_fd +.PHONY: T12725 +T12725: + '$(TEST_CC)' ok.c -o ok.exe + '$(TEST_CC)' main.c -o main.exe diff --git a/tests/T9775/T9775_fail.hs b/tests/T9775/T9775_fail.hs new file mode 100644 index 0000000..8aaca8c --- /dev/null +++ b/tests/T9775/T9775_fail.hs @@ -0,0 +1,8 @@ +module Main where + +import System.Process + +main + = do (_,_,_,p) <- createProcess_ "T9775_fail" (proc "main" "") + waitForProcess p >> print + \ No newline at end of file diff --git a/tests/T9775/all.T b/tests/T9775/all.T new file mode 100644 index 0000000..dbccb29 --- /dev/null +++ b/tests/T9775/all.T @@ -0,0 +1,6 @@ + +test('T12725_fail', + [extra_clean(['ok.o', 'ok.exe', 'main.o', 'main.exe']), + [unless(opsys('mingw32'),skip)] + pre_cmd('$MAKE -s --no-print-directory T12725')], + compile_and_run, ['']) diff --git a/tests/T9775/main.c b/tests/T9775/main.c new file mode 100644 index 0000000..cc27edb --- /dev/null +++ b/tests/T9775/main.c @@ -0,0 +1,6 @@ +#include + +int main(int argc, char *argv[]) { + char * args[2] = { "ok", NULL }; + execv("./ok", args); +} diff --git a/tests/T9775/ok.c b/tests/T9775/ok.c new file mode 100644 index 0000000..dcd08c4 --- /dev/null +++ b/tests/T9775/ok.c @@ -0,0 +1,6 @@ +#include + +int main() { + printf("ok\n"); + return 0; +} From git at git.haskell.org Wed Jul 19 21:18:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:48 +0000 (UTC) Subject: [commit: packages/process] master: GH77: Replaced system and rawSystem (f6de652) Message-ID: <20170719211848.E72823A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f6de6523e27c42ad8e92a375239dbfe8772e2b7e/process >--------------------------------------------------------------- commit f6de6523e27c42ad8e92a375239dbfe8772e2b7e Author: Tamar Christina Date: Sun Dec 4 17:20:45 2016 +0000 GH77: Replaced system and rawSystem >--------------------------------------------------------------- f6de6523e27c42ad8e92a375239dbfe8772e2b7e System/Process.hs | 25 ++++++++++++++++++++----- System/Process/Internals.hs | 33 ++++++++++++++++++++++++++++++++- 2 files changed, 52 insertions(+), 6 deletions(-) diff --git a/System/Process.hs b/System/Process.hs index 0fc3445..44a4362 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -43,6 +43,7 @@ module System.Process ( readCreateProcessWithExitCode, readProcessWithExitCode, withCreateProcess, + executeAndWait, -- ** Related utilities showCommandForUser, @@ -852,9 +853,7 @@ when the process died as the result of a signal. -} system :: String -> IO ExitCode system "" = ioException (ioeSetErrorString (mkIOError InvalidArgument "system" Nothing Nothing) "null command") -system str = do - (_,_,_,p) <- createProcess_ "system" (shell str) { delegate_ctlc = True } - waitForProcess p +system str = executeAndWait "system" (shell str) { delegate_ctlc = True } --TODO: in a later release {-# DEPRECATED rawSystem "Use 'callProcess' (or 'spawnProcess' and 'waitForProcess') instead" #-} @@ -868,6 +867,22 @@ It will therefore behave more portably between operating systems than 'system'. The return codes and possible failures are the same as for 'system'. -} rawSystem :: String -> [String] -> IO ExitCode -rawSystem cmd args = do - (_,_,_,p) <- createProcess_ "rawSystem" (proc cmd args) { delegate_ctlc = True } +rawSystem cmd args = executeAndWait "rawSystem" (proc cmd args) { delegate_ctlc = True } + +-- --------------------------------------------------------------------------- +-- executeAndWait + +-- | Create a new process and wait for it's termination. +-- +-- @since 1.4.?.? +executeAndWait :: String -> CreateProcess -> IO ExitCode +executeAndWait name proc_ = do +#if defined(WINDOWS) + (_,_,_,_,Just job,Just iocp) <- createProcessExt_ name True proc_ + maybe (ExitFailure (-1)) mkExitCode <$> waitForJobCompletion job iocp (-1) + where mkExitCode code | code == 0 = ExitSuccess + | otherwise = ExitFailure $ fromIntegral code +#else + (_,_,_,p) <- createProcess_ name proc_ waitForProcess p +#endif \ No newline at end of file diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index fad7c92..1ee8f5c 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -43,6 +43,7 @@ module System.Process.Internals ( createPipe, createPipeFd, interruptProcessGroupOf, + createProcessExt_, ) where import Foreign.C @@ -60,7 +61,6 @@ import System.Process.Posix #endif -- ---------------------------------------------------------------------------- - -- | This function is almost identical to -- 'System.Process.createProcess'. The only differences are: -- @@ -81,6 +81,37 @@ createProcess_ createProcess_ = createProcess_Internal {-# INLINE createProcess_ #-} +-- ---------------------------------------------------------------------------- +-- | This function is almost identical to +-- 'createProcess_'. The only differences are: +-- +-- * A boolean argument can be given in order to create an I/O cp port to monitor +-- a process tree's progress on Windows. +-- +-- The function also returns two new handles: +-- * an I/O Completion Port handle on which events +-- will be signaled. +-- * a Job handle which can be used to kill all running +-- processes. +-- +-- On POSIX platforms these two new handles will always be Nothing +-- +-- @since 1.4.?.? +createProcessExt_ + :: String -- ^ function name (for error messages) + -> Bool -- ^ Use I/O CP port for monitoring + -> CreateProcess + -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle, + Maybe ProcessHandle, Maybe ProcessHandle) +#ifdef WINDOWS +createProcessExt_ = createProcess_Internal_ext +#else +createProcessExt_ name _ proc_ + = do (hndStdInput, hndStdOutput, hndStdError, ph) <- createProcess_ nme proc_ + return ((hndStdInput, hndStdOutput, hndStdError, ph, Nothing, Nothing) +#endif +{-# INLINE createProcessExt_ #-} + -- ------------------------------------------------------------------------ -- Escaping commands for shells From git at git.haskell.org Wed Jul 19 21:18:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:55 +0000 (UTC) Subject: [commit: packages/process] master: rebased and set back WINDOWS_CCONV (f8b53d8) Message-ID: <20170719211855.06C183A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f8b53d8db973ecabaeaf5ae5b1332734fccf1419/process >--------------------------------------------------------------- commit f8b53d8db973ecabaeaf5ae5b1332734fccf1419 Author: Tamar Christina Date: Sun Jan 29 21:06:58 2017 +0000 rebased and set back WINDOWS_CCONV >--------------------------------------------------------------- f8b53d8db973ecabaeaf5ae5b1332734fccf1419 System/Process/Windows.hsc | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/System/Process/Windows.hsc b/System/Process/Windows.hsc index 07c4f0d..ff8d3a7 100644 --- a/System/Process/Windows.hsc +++ b/System/Process/Windows.hsc @@ -44,10 +44,17 @@ import System.Win32.Process (getProcessId) -- The double hash is used so that hsc does not process this include file ##include "processFlags.h" -#include "windows_cconv.h" #include /* for _O_BINARY */ +##if defined(i386_HOST_ARCH) +## define WINDOWS_CCONV stdcall +##elif defined(x86_64_HOST_ARCH) +## define WINDOWS_CCONV ccall +##else +## error Unknown mingw32 arch +##endif + throwErrnoIfBadPHandle :: String -> IO PHANDLE -> IO PHANDLE throwErrnoIfBadPHandle = throwErrnoIfNull From git at git.haskell.org Wed Jul 19 21:18:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:50 +0000 (UTC) Subject: [commit: packages/process] master: GH77: Fixed compilation (8080309) Message-ID: <20170719211850.ED77A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/80803096e76ee580bd255b5e9acc11ede2ed2690/process >--------------------------------------------------------------- commit 80803096e76ee580bd255b5e9acc11ede2ed2690 Author: Tamar Christina Date: Sun Dec 4 08:15:39 2016 +0000 GH77: Fixed compilation >--------------------------------------------------------------- 80803096e76ee580bd255b5e9acc11ede2ed2690 System/Process/Windows.hsc | 26 ++++++++++++++------------ cbits/runProcess.c | 12 +++++++++--- changelog.md | 1 + 3 files changed, 24 insertions(+), 15 deletions(-) diff --git a/System/Process/Windows.hsc b/System/Process/Windows.hsc index 6347dad..c1294fa 100644 --- a/System/Process/Windows.hsc +++ b/System/Process/Windows.hsc @@ -1,4 +1,5 @@ -{-# LANGUAGE CPP #-} +{-# LANGUAGE CPP, ForeignFunctionInterface #-} +{-# LANGUAGE InterruptibleFFI #-} module System.Process.Windows ( mkProcessHandle , translateInternal @@ -57,7 +58,7 @@ mkProcessHandle h = do mkProcessHandle' :: PHANDLE -> IO (Maybe ProcessHandle) mkProcessHandle' h = do if h /= nullPtr - then return $ Just $ mkProcessHandle h + then Just <$> mkProcessHandle h else return $ Nothing processHandleFinaliser :: MVar ProcessHandle__ -> IO () @@ -90,8 +91,8 @@ createProcess_Internal -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) createProcess_Internal fun cp - = let (hndStdInput, hndStdOutput, hndStdError, ph, _, _) = createProcess_Internal_ext fun cp - in return (hndStdInput, hndStdOutput, hndStdError, ph) + = do (hndStdInput, hndStdOutput, hndStdError, ph, _, _) <- createProcess_Internal_ext fun False cp + return (hndStdInput, hndStdOutput, hndStdError, ph) createProcess_Internal_ext :: String -- ^ function name (for error messages) @@ -101,7 +102,7 @@ createProcess_Internal_ext Maybe Handle, ProcessHandle, Maybe ProcessHandle, Maybe ProcessHandle) -createProcess_Internal fun useJob CreateProcess{ cmdspec = cmdsp, +createProcess_Internal_ext fun useJob CreateProcess{ cmdspec = cmdsp, cwd = mb_cwd, env = mb_env, std_in = mb_stdin, @@ -114,13 +115,14 @@ createProcess_Internal fun useJob CreateProcess{ cmdspec = cmdsp, create_new_console = mb_create_new_console, new_session = mb_new_session } = do + let lenPtr = sizeOf (undefined :: WordPtr) (cmd, cmdline) <- commandToProcess cmdsp withFilePathException cmd $ - alloca $ \ pfdStdInput -> - alloca $ \ pfdStdOutput -> - alloca $ \ pfdStdError -> - alloca $ \ hJob -> - alloca $ \ hIOcpPort -> + alloca $ \ pfdStdInput -> + alloca $ \ pfdStdOutput -> + alloca $ \ pfdStdError -> + allocaBytes lenPtr $ \ hJob -> + allocaBytes lenPtr $ \ hIOcpPort -> maybeWith withCEnvironment mb_env $ \pEnv -> maybeWith withCWString mb_cwd $ \pWorkDir -> do withCWString cmdline $ \pcmdline -> do @@ -160,7 +162,7 @@ createProcess_Internal fun useJob CreateProcess{ cmdspec = cmdsp, ph <- mkProcessHandle proc_handle phJob <- mkProcessHandle' hJob phIOCP <- mkProcessHandle' hIOcpPort - return (hndStdInput, hndStdOutput, hndStdError, ph) + return (hndStdInput, hndStdOutput, hndStdError, ph, phJob, phIOCP) {-# NOINLINE runInteractiveProcess_lock #-} runInteractiveProcess_lock :: MVar () @@ -192,7 +194,7 @@ foreign import ccall unsafe "terminateJob" foreign import ccall interruptible "waitForJobCompletion" -- NB. safe - can block c_waitForJobCompletion :: PHANDLE - :: PHANDLE + -> PHANDLE -> CInt -> Ptr CInt -> IO CInt diff --git a/cbits/runProcess.c b/cbits/runProcess.c index b8feecf..b60bf07 100644 --- a/cbits/runProcess.c +++ b/cbits/runProcess.c @@ -520,8 +520,14 @@ createJob () // Last process in the job terminates. This prevent half dead processes. jeli.BasicLimitInformation.LimitFlags = JOB_OBJECT_LIMIT_KILL_ON_JOB_CLOSE; - return SetInformationJobObject(hJob, JobObjectExtendedLimitInformation, - &jeli, sizeof(JOBOBJECT_EXTENDED_LIMIT_INFORMATION)); + if (SetInformationJobObject (hJob, JobObjectExtendedLimitInformation, + &jeli, sizeof(JOBOBJECT_EXTENDED_LIMIT_INFORMATION))) + { + return hJob; + } + + maperrno(); + return NULL; } static HANDLE @@ -782,7 +788,7 @@ waitForProcess (ProcHandle handle, int *pret) return -1; } -static int +int waitForJobCompletion (HANDLE hJob, HANDLE ioPort, DWORD timeout, int *pExitCode) { DWORD CompletionCode; diff --git a/changelog.md b/changelog.md index 73c1814..a8e7738 100644 --- a/changelog.md +++ b/changelog.md @@ -10,6 +10,7 @@ * New exposed `withCreateProcess` * Derive `Show` and `Eq` for `CreateProcess`, `CmdSpec`, and `StdStream` +* Add support for monitoring process tree for termination with `...` ## 1.4.2.0 *January 2016* From git at git.haskell.org Wed Jul 19 21:18:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:52 +0000 (UTC) Subject: [commit: packages/process] master: Updated based on review (0f7b948) Message-ID: <20170719211853.005DC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0f7b9483a11a51bd8f2941f590f22b5f91fb1df7/process >--------------------------------------------------------------- commit 0f7b9483a11a51bd8f2941f590f22b5f91fb1df7 Author: Tamar Christina Date: Sun Jan 29 20:52:53 2017 +0000 Updated based on review >--------------------------------------------------------------- 0f7b9483a11a51bd8f2941f590f22b5f91fb1df7 System/Process.hs | 24 ++++++++++++------------ System/Process/Common.hs | 4 ++-- System/Process/Internals.hs | 10 +++++----- System/Process/Windows.hsc | 9 +-------- changelog.md | 4 ++-- process.cabal | 2 +- 6 files changed, 23 insertions(+), 30 deletions(-) diff --git a/System/Process.hs b/System/Process.hs index a0574e4..53c1f21 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -596,8 +596,8 @@ waitForProcess ph@(ProcessHandle _ delegating_ctlc) = do throwErrnoIfMinus1Retry_ "waitForProcess" (c_waitForProcess h pret) modifyProcessHandle ph $ \p_' -> case p_' of - ClosedHandle e -> return (p_',e) - OpenExtHandle{} -> error "waitForProcess handle mismatch." + ClosedHandle e -> return (p_', e) + OpenExtHandle{} -> return (p_', ExitFailure (-1)) OpenHandle ph' -> do closePHANDLE ph' code <- peek pret @@ -608,13 +608,13 @@ waitForProcess ph@(ProcessHandle _ delegating_ctlc) = do when delegating_ctlc $ endDelegateControlC e return e - OpenExtHandle _ job iocp -> do + OpenExtHandle _ job iocp -> #if defined(WINDOWS) maybe (ExitFailure (-1)) mkExitCode `fmap` waitForJobCompletion job iocp timeout_Infinite where mkExitCode code | code == 0 = ExitSuccess | otherwise = ExitFailure $ fromIntegral code #else - error "OpenExtHandle should not happen on POSIX." + return $ ExitFailure (-1) #endif -- ---------------------------------------------------------------------------- @@ -635,14 +635,14 @@ getProcessExitCode ph@(ProcessHandle _ delegating_ctlc) = do case p_ of ClosedHandle e -> return (p_, (Just e, False)) open -> do - let h = getHandle open alloca $ \pExitCode -> do - res <- throwErrnoIfMinus1Retry "getProcessExitCode" $ - c_getProcessExitCode h pExitCode - code <- peek pExitCode + res <- let getCode h = throwErrnoIfMinus1Retry "getProcessExitCode" $ + c_getProcessExitCode h pExitCode + in maybe (return 0) getCode $ getHandle open if res == 0 then return (p_, (Nothing, False)) else do + code <- peek pExitCode closePHANDLE h let e | code == 0 = ExitSuccess | otherwise = ExitFailure (fromIntegral code) @@ -651,10 +651,10 @@ getProcessExitCode ph@(ProcessHandle _ delegating_ctlc) = do Just e | was_open && delegating_ctlc -> endDelegateControlC e _ -> return () return m_e - where getHandle :: ProcessHandle__ -> PHANDLE - getHandle (OpenHandle h) = h - getHandle (ClosedHandle _) = error "getHandle: handle closed." - getHandle (OpenExtHandle h _ _) = h + where getHandle :: ProcessHandle__ -> Maybe PHANDLE + getHandle (OpenHandle h) = Just h + getHandle (ClosedHandle _) = Nothing + getHandle (OpenExtHandle h _ _) = Just h -- ---------------------------------------------------------------------------- diff --git a/System/Process/Common.hs b/System/Process/Common.hs index 0f70f7a..b2caae6 100644 --- a/System/Process/Common.hs +++ b/System/Process/Common.hs @@ -101,11 +101,11 @@ data CreateProcess = CreateProcess{ -- -- @since 1.4.0.0 use_process_jobs :: Bool -- ^ On Windows systems this flag indicates that we should wait for the entire process tree - -- to finish before unblocking. On POSIX system this flag is ignored. + -- to finish before unblocking. On POSIX systems this flag is ignored. -- -- Default: @False@ -- - -- @since 1.x.x.x + -- @since 1.5.0.0 } deriving (Show, Eq) -- | contains the handles returned by a call to createProcess_Internal diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index 026cd99..036e1c0 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -32,13 +32,13 @@ module System.Process.Internals ( endDelegateControlC, stopDelegateControlC, unwrapHandles, -#ifndef WINDOWS - pPrPr_disableITimers, c_execvpe, - ignoreSignal, defaultSignal, -#else +#ifdef WINDOWS terminateJob, waitForJobCompletion, timeout_Infinite, +#else + pPrPr_disableITimers, c_execvpe, + ignoreSignal, defaultSignal, #endif withFilePathException, withCEnvironment, translate, @@ -70,7 +70,7 @@ import System.Process.Posix -- * This function takes an extra @String@ argument to be used in creating -- error messages. -- --- * 'use_process_jobs' can set in CreateProcess since 1.4.?.? in order to create +-- * 'use_process_jobs' can be set in CreateProcess since 1.5.0.0 in order to create -- an I/O completion port to monitor a process tree's progress on Windows. -- -- The function also returns two new handles: diff --git a/System/Process/Windows.hsc b/System/Process/Windows.hsc index ff8d3a7..07c4f0d 100644 --- a/System/Process/Windows.hsc +++ b/System/Process/Windows.hsc @@ -44,17 +44,10 @@ import System.Win32.Process (getProcessId) -- The double hash is used so that hsc does not process this include file ##include "processFlags.h" +#include "windows_cconv.h" #include /* for _O_BINARY */ -##if defined(i386_HOST_ARCH) -## define WINDOWS_CCONV stdcall -##elif defined(x86_64_HOST_ARCH) -## define WINDOWS_CCONV ccall -##else -## error Unknown mingw32 arch -##endif - throwErrnoIfBadPHandle :: String -> IO PHANDLE -> IO PHANDLE throwErrnoIfBadPHandle = throwErrnoIfNull diff --git a/changelog.md b/changelog.md index 991be99..bee8874 100644 --- a/changelog.md +++ b/changelog.md @@ -5,13 +5,13 @@ * Bug fix: Don't close already closed pipes [#81](https://github.com/haskell/process/pull/81) * Relax version bounds of Win32 to allow 2.5. +* Add support for monitoring process tree for termination with the parameter `use_process_jobs` + in `CreateProcess` on Windows. Also added a function `terminateJob` to kill entire process tree. ## 1.4.3.0 *December 2016* * New exposed `withCreateProcess` * Derive `Show` and `Eq` for `CreateProcess`, `CmdSpec`, and `StdStream` -* Add support for monitoring process tree for termination with the parameter `use_process_jobs` - in `CreateProcess` on Windows. Also added a function `terminateJob` to kill entire process tree. ## 1.4.2.0 *January 2016* diff --git a/process.cabal b/process.cabal index b339938..0ef5b91 100644 --- a/process.cabal +++ b/process.cabal @@ -1,5 +1,5 @@ name: process -version: 1.4.3.1 +version: 1.5.0.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE From git at git.haskell.org Wed Jul 19 21:18:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:57 +0000 (UTC) Subject: [commit: packages/process] master: fix build. (9bcbaeb) Message-ID: <20170719211857.0DD193A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9bcbaeb7bd53d10087ebedd53b1d87efac814aac/process >--------------------------------------------------------------- commit 9bcbaeb7bd53d10087ebedd53b1d87efac814aac Author: Tamar Christina Date: Sun Jan 29 21:48:24 2017 +0000 fix build. >--------------------------------------------------------------- 9bcbaeb7bd53d10087ebedd53b1d87efac814aac System/Process.hs | 24 +++++++++++++----------- 1 file changed, 13 insertions(+), 11 deletions(-) diff --git a/System/Process.hs b/System/Process.hs index 53c1f21..81a5788 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -636,17 +636,19 @@ getProcessExitCode ph@(ProcessHandle _ delegating_ctlc) = do ClosedHandle e -> return (p_, (Just e, False)) open -> do alloca $ \pExitCode -> do - res <- let getCode h = throwErrnoIfMinus1Retry "getProcessExitCode" $ - c_getProcessExitCode h pExitCode - in maybe (return 0) getCode $ getHandle open - if res == 0 - then return (p_, (Nothing, False)) - else do - code <- peek pExitCode - closePHANDLE h - let e | code == 0 = ExitSuccess - | otherwise = ExitFailure (fromIntegral code) - return (ClosedHandle e, (Just e, True)) + case getHandle open of + Nothing -> return (p_, (Nothing, False)) + Just h -> do + res <- throwErrnoIfMinus1Retry "getProcessExitCode" $ + c_getProcessExitCode h pExitCode + code <- peek pExitCode + if res == 0 + then return (p_, (Nothing, False)) + else do + closePHANDLE h + let e | code == 0 = ExitSuccess + | otherwise = ExitFailure (fromIntegral code) + return (ClosedHandle e, (Just e, True)) case m_e of Just e | was_open && delegating_ctlc -> endDelegateControlC e _ -> return () From git at git.haskell.org Wed Jul 19 21:18:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:46 +0000 (UTC) Subject: [commit: packages/process] master: GH77: Updated readme (3f440e2) Message-ID: <20170719211846.E0CF83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3f440e22f658caed0ff42645610d84ff51dd3258/process >--------------------------------------------------------------- commit 3f440e22f658caed0ff42645610d84ff51dd3258 Author: Tamar Christina Date: Sun Dec 4 17:21:40 2016 +0000 GH77: Updated readme >--------------------------------------------------------------- 3f440e22f658caed0ff42645610d84ff51dd3258 changelog.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index 3fd77f8..f5ab09a 100644 --- a/changelog.md +++ b/changelog.md @@ -11,7 +11,7 @@ * New exposed `withCreateProcess` * Derive `Show` and `Eq` for `CreateProcess`, `CmdSpec`, and `StdStream` * Add support for monitoring process tree for termination with `createProcess_Internal_ext` - , `terminateJob` and `waitForJobCompletion`. + , `terminateJob`, `waitForJobCompletion` and a new generic function `executeAndWait`. ## 1.4.2.0 *January 2016* From git at git.haskell.org Wed Jul 19 21:18:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:18:59 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #80 from Mistuke/gh-77-create-process-hook (d3d637d) Message-ID: <20170719211859.15F1E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d3d637d2b01748d9807f51f4bb475573a55b24e5/process >--------------------------------------------------------------- commit d3d637d2b01748d9807f51f4bb475573a55b24e5 Merge: 0524859 9bcbaeb Author: Michael Snoyman Date: Mon Jan 30 14:29:49 2017 +0200 Merge pull request #80 from Mistuke/gh-77-create-process-hook Add new API that can correctly wait for termination of processes forked with exec on Windows. >--------------------------------------------------------------- d3d637d2b01748d9807f51f4bb475573a55b24e5 System/Process.hs | 58 ++++--- System/Process/Common.hs | 25 ++- System/Process/Internals.hs | 28 +++- System/Process/Posix.hs | 13 +- System/Process/Windows.hsc | 167 +++++++++++++++----- cbits/runProcess.c | 196 +++++++++++++++++++++++- changelog.md | 2 + include/runProcess.h | 12 +- process.cabal | 2 +- tests/{ => T9775}/Makefile | 9 +- tests/T9775/T9775_fail.hs | 7 + tests/{T4889.stdout => T9775/T9775_fail.stdout} | 2 +- tests/T9775/T9775_good.hs | 7 + tests/T9775/T9775_good.stdout | 2 + tests/T9775/all.T | 14 ++ tests/T9775/main.c | 6 + tests/T9775/ok.c | 8 + 17 files changed, 483 insertions(+), 75 deletions(-) From git at git.haskell.org Wed Jul 19 21:19:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:01 +0000 (UTC) Subject: [commit: packages/process] master: Update Common.hs (78a9636) Message-ID: <20170719211901.1C7333A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/78a963699d8fd470591802987890aa69a2a0f2de/process >--------------------------------------------------------------- commit 78a963699d8fd470591802987890aa69a2a0f2de Author: James Cheney Date: Mon Jan 30 14:38:58 2017 +0000 Update Common.hs #87 >--------------------------------------------------------------- 78a963699d8fd470591802987890aa69a2a0f2de System/Process/Common.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Process/Common.hs b/System/Process/Common.hs index b2caae6..3c8d370 100644 --- a/System/Process/Common.hs +++ b/System/Process/Common.hs @@ -66,7 +66,7 @@ type PHANDLE = CPid #endif data CreateProcess = CreateProcess{ - cmdspec :: CmdSpec, -- ^ Executable & arguments, or shell command. Relative paths are resolved with respect to 'cwd' if given, and otherwise the current working directory. + cmdspec :: CmdSpec, -- ^ Executable & arguments, or shell command. If 'cwd' is 'Nothing', relative paths are resolved with respect to the current working directory. If 'cwd' is provided, it is implementation-dependent whether relative paths are resolved with respect to 'cwd' or the current working directory, so absolute paths should be used to ensure portability. cwd :: Maybe FilePath, -- ^ Optional path to the working directory for the new process env :: Maybe [(String,String)], -- ^ Optional environment (otherwise inherit from the current process) std_in :: StdStream, -- ^ How to determine stdin From git at git.haskell.org Wed Jul 19 21:19:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:03 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #88 from jamescheney/patch-1 (54a19f5) Message-ID: <20170719211903.236673A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/54a19f5b82ab4d70d863568a65b852b456a65270/process >--------------------------------------------------------------- commit 54a19f5b82ab4d70d863568a65b852b456a65270 Merge: d3d637d 78a9636 Author: Michael Snoyman Date: Mon Jan 30 16:49:09 2017 +0200 Merge pull request #88 from jamescheney/patch-1 Update Common.hs >--------------------------------------------------------------- 54a19f5b82ab4d70d863568a65b852b456a65270 System/Process/Common.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Wed Jul 19 21:19:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:05 +0000 (UTC) Subject: [commit: packages/process] master: Fix bug in multi-threaded waitForProcess (5b99d45) Message-ID: <20170719211905.29C953A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5b99d45103d1edf6f596c353f548221d897db4cf/process >--------------------------------------------------------------- commit 5b99d45103d1edf6f596c353f548221d897db4cf Author: Charles Cooper Date: Sat Apr 2 17:42:56 2016 -0400 Fix bug in multi-threaded waitForProcess Previously an exception was being thrown when multiple threads were blocking on waitForProcess due to inconsistent handling of the return code of `waitpid`: "If more than one thread is suspended in waitpid() awaiting termination of the same process, exactly one thread returns the process status at the time of the target child process termination. The other threads return -1, with errno set to ECHILD." `getProcessExitCode` was handling the ECHILD case by returning 1, but `waitForProcess` was returning (-1) in all cases. For consistency this commit follows the approach in getProcessExitCode, returning 1 to the caller of c_waitForProcess if errno is ECHILD, thus avoiding throwing an exception in the calling code. >--------------------------------------------------------------- 5b99d45103d1edf6f596c353f548221d897db4cf cbits/runProcess.c | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/cbits/runProcess.c b/cbits/runProcess.c index ae184c8..1e97ad1 100644 --- a/cbits/runProcess.c +++ b/cbits/runProcess.c @@ -425,6 +425,11 @@ int waitForProcess (ProcHandle handle, int *pret) if (waitpid(handle, &wstat, 0) < 0) { + if (errno == ECHILD) + { + *pret = 0; + return 1; + } return -1; } From git at git.haskell.org Wed Jul 19 21:19:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:07 +0000 (UTC) Subject: [commit: packages/process] master: Revert "Fix bug in multi-threaded waitForProcess" (4575acb) Message-ID: <20170719211907.309BF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4575acb4919f24c95b14e346e32daa1103147791/process >--------------------------------------------------------------- commit 4575acb4919f24c95b14e346e32daa1103147791 Author: Charles Cooper Date: Fri Feb 3 10:09:20 2017 -0500 Revert "Fix bug in multi-threaded waitForProcess" This reverts commit d67484fe64a9a42e7daf944a9396b4ec46c060f3. >--------------------------------------------------------------- 4575acb4919f24c95b14e346e32daa1103147791 cbits/runProcess.c | 5 ----- 1 file changed, 5 deletions(-) diff --git a/cbits/runProcess.c b/cbits/runProcess.c index 1e97ad1..ae184c8 100644 --- a/cbits/runProcess.c +++ b/cbits/runProcess.c @@ -425,11 +425,6 @@ int waitForProcess (ProcHandle handle, int *pret) if (waitpid(handle, &wstat, 0) < 0) { - if (errno == ECHILD) - { - *pret = 0; - return 1; - } return -1; } From git at git.haskell.org Wed Jul 19 21:19:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:09 +0000 (UTC) Subject: [commit: packages/process] master: Fix waitpid race by adding a lock (d837c95) Message-ID: <20170719211909.37CA23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d837c95d378c16e74d2dcbb09a75ca907eb018d1/process >--------------------------------------------------------------- commit d837c95d378c16e74d2dcbb09a75ca907eb018d1 Author: Charles Cooper Date: Fri Feb 3 10:41:05 2017 -0500 Fix waitpid race by adding a lock >--------------------------------------------------------------- d837c95d378c16e74d2dcbb09a75ca907eb018d1 System/Process.hs | 12 +++++------- System/Process/Common.hs | 10 +++++++--- System/Process/Posix.hs | 3 ++- 3 files changed, 14 insertions(+), 11 deletions(-) diff --git a/System/Process.hs b/System/Process.hs index 81a5788..b78b831 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -237,7 +237,7 @@ withCreateProcess_ fun c action = cleanupProcess :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO () cleanupProcess (mb_stdin, mb_stdout, mb_stderr, - ph@(ProcessHandle _ delegating_ctlc)) = do + ph@(ProcessHandle _ delegating_ctlc _)) = do terminateProcess ph -- Note, it's important that other threads that might be reading/writing -- these handles also get killed off, since otherwise they might be holding @@ -258,7 +258,7 @@ cleanupProcess (mb_stdin, mb_stdout, mb_stderr, _ <- forkIO (waitForProcess (resetCtlcDelegation ph) >> return ()) return () where - resetCtlcDelegation (ProcessHandle m _) = ProcessHandle m False + resetCtlcDelegation (ProcessHandle m _ l) = ProcessHandle m False l -- ---------------------------------------------------------------------------- -- spawnProcess/spawnCommand @@ -584,14 +584,11 @@ detail. waitForProcess :: ProcessHandle -> IO ExitCode -waitForProcess ph@(ProcessHandle _ delegating_ctlc) = do +waitForProcess ph@(ProcessHandle _ delegating_ctlc _) = lockWaitpid $ do p_ <- modifyProcessHandle ph $ \p_ -> return (p_,p_) case p_ of ClosedHandle e -> return e OpenHandle h -> do - -- don't hold the MVar while we call c_waitForProcess... - -- (XXX but there's a small race window here during which another - -- thread could close the handle or call waitForProcess) e <- alloca $ \pret -> do throwErrnoIfMinus1Retry_ "waitForProcess" (c_waitForProcess h pret) modifyProcessHandle ph $ \p_' -> @@ -616,6 +613,7 @@ waitForProcess ph@(ProcessHandle _ delegating_ctlc) = do #else return $ ExitFailure (-1) #endif + where lockWaitpid m = withMVar (waitpidLock ph) $ \() -> m -- ---------------------------------------------------------------------------- -- getProcessExitCode @@ -630,7 +628,7 @@ when the process died as the result of a signal. -} getProcessExitCode :: ProcessHandle -> IO (Maybe ExitCode) -getProcessExitCode ph@(ProcessHandle _ delegating_ctlc) = do +getProcessExitCode ph@(ProcessHandle _ delegating_ctlc _) = do (m_e, was_open) <- modifyProcessHandle ph $ \p_ -> case p_ of ClosedHandle e -> return (p_, (Just e, False)) diff --git a/System/Process/Common.hs b/System/Process/Common.hs index 3c8d370..dd09c0e 100644 --- a/System/Process/Common.hs +++ b/System/Process/Common.hs @@ -177,7 +177,11 @@ data StdStream data ProcessHandle__ = OpenHandle PHANDLE | OpenExtHandle PHANDLE PHANDLE PHANDLE | ClosedHandle ExitCode -data ProcessHandle = ProcessHandle !(MVar ProcessHandle__) !Bool +data ProcessHandle + = ProcessHandle { phandle :: !(MVar ProcessHandle__) + , mb_delegate_ctlc :: !Bool + , waitpidLock :: !(MVar ()) + } withFilePathException :: FilePath -> IO a -> IO a withFilePathException fpath act = handle mapEx act @@ -188,13 +192,13 @@ modifyProcessHandle :: ProcessHandle -> (ProcessHandle__ -> IO (ProcessHandle__, a)) -> IO a -modifyProcessHandle (ProcessHandle m _) io = modifyMVar m io +modifyProcessHandle (ProcessHandle m _ _) io = modifyMVar m io withProcessHandle :: ProcessHandle -> (ProcessHandle__ -> IO a) -> IO a -withProcessHandle (ProcessHandle m _) io = withMVar m io +withProcessHandle (ProcessHandle m _ _) io = withMVar m io fd_stdin, fd_stdout, fd_stderr :: FD fd_stdin = 0 diff --git a/System/Process/Posix.hs b/System/Process/Posix.hs index cd8573f..129072f 100644 --- a/System/Process/Posix.hs +++ b/System/Process/Posix.hs @@ -48,7 +48,8 @@ import System.Process.Common mkProcessHandle :: PHANDLE -> Bool -> IO ProcessHandle mkProcessHandle p mb_delegate_ctlc = do m <- newMVar (OpenHandle p) - return (ProcessHandle m mb_delegate_ctlc) + l <- newMVar () + return (ProcessHandle m mb_delegate_ctlc l) closePHANDLE :: PHANDLE -> IO () closePHANDLE _ = return () From git at git.haskell.org Wed Jul 19 21:19:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:13 +0000 (UTC) Subject: [commit: packages/process] master: Compile for windows (b2360d9) Message-ID: <20170719211913.447933A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b2360d9f2260df494c8ddb90db6085476e59302e/process >--------------------------------------------------------------- commit b2360d9f2260df494c8ddb90db6085476e59302e Author: Charles Cooper Date: Fri Feb 3 10:59:22 2017 -0500 Compile for windows >--------------------------------------------------------------- b2360d9f2260df494c8ddb90db6085476e59302e System/Process/Windows.hsc | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/System/Process/Windows.hsc b/System/Process/Windows.hsc index ff8d3a7..6c92b02 100644 --- a/System/Process/Windows.hsc +++ b/System/Process/Windows.hsc @@ -66,7 +66,8 @@ mkProcessHandle h job io = do then newMVar (OpenHandle h) else newMVar (OpenExtHandle h job io) _ <- mkWeakMVar m (processHandleFinaliser m) - return (ProcessHandle m False) + l <- newMVar () + return (ProcessHandle m False l) processHandleFinaliser :: MVar ProcessHandle__ -> IO () processHandleFinaliser m = From git at git.haskell.org Wed Jul 19 21:19:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:15 +0000 (UTC) Subject: [commit: packages/process] master: Add comments (3f3566f) Message-ID: <20170719211915.4B37E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3f3566f23539863cf1d6e45261651fa4a46ff5b9/process >--------------------------------------------------------------- commit 3f3566f23539863cf1d6e45261651fa4a46ff5b9 Author: Charles Cooper Date: Sat Feb 4 15:39:42 2017 -0500 Add comments >--------------------------------------------------------------- 3f3566f23539863cf1d6e45261651fa4a46ff5b9 System/Process.hs | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/System/Process.hs b/System/Process.hs index b78b831..50c787e 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -590,6 +590,7 @@ waitForProcess ph@(ProcessHandle _ delegating_ctlc _) = lockWaitpid $ do ClosedHandle e -> return e OpenHandle h -> do e <- alloca $ \pret -> do + -- don't hold the MVar while we call c_waitForProcess... throwErrnoIfMinus1Retry_ "waitForProcess" (c_waitForProcess h pret) modifyProcessHandle ph $ \p_' -> case p_' of @@ -613,7 +614,13 @@ waitForProcess ph@(ProcessHandle _ delegating_ctlc _) = lockWaitpid $ do #else return $ ExitFailure (-1) #endif - where lockWaitpid m = withMVar (waitpidLock ph) $ \() -> m + where + -- If more than one thread calls `waitpid` at a time, `waitpid` will + -- return the exit code to one of them and (-1) to the rest of them, + -- causing an exception to be thrown. + -- Cf. https://github.com/haskell/process/issues/46, and + -- https://github.com/haskell/process/pull/58 for further discussion + lockWaitpid m = withMVar (waitpidLock ph) $ \() -> m -- ---------------------------------------------------------------------------- -- getProcessExitCode From git at git.haskell.org Wed Jul 19 21:19:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:11 +0000 (UTC) Subject: [commit: packages/process] master: Test multithreaded bug (962d5f1) Message-ID: <20170719211911.3E59B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/962d5f14d2bb4fda38d8bba689952076a3080213/process >--------------------------------------------------------------- commit 962d5f14d2bb4fda38d8bba689952076a3080213 Author: Charles Cooper Date: Fri Feb 3 10:33:05 2017 -0500 Test multithreaded bug >--------------------------------------------------------------- 962d5f14d2bb4fda38d8bba689952076a3080213 process.cabal | 2 ++ test/main.hs | 15 ++++++++++++++- 2 files changed, 16 insertions(+), 1 deletion(-) diff --git a/process.cabal b/process.cabal index 0ef5b91..30d25bb 100644 --- a/process.cabal +++ b/process.cabal @@ -82,3 +82,5 @@ test-suite test , bytestring , directory , process + ghc-options: -threaded + -with-rtsopts "-N" diff --git a/test/main.hs b/test/main.hs index 9ea0524..f89f3ef 100644 --- a/test/main.hs +++ b/test/main.hs @@ -1,10 +1,12 @@ import Control.Exception -import Control.Monad (unless) +import Control.Monad (unless, void) import System.Exit import System.IO.Error import System.Directory (getCurrentDirectory, setCurrentDirectory) import System.Process +import Control.Concurrent import Data.List (isInfixOf) +import Data.Maybe (isNothing) import System.IO (hClose, openBinaryTempFile) import qualified Data.ByteString as S import qualified Data.ByteString.Char8 as S8 @@ -66,6 +68,17 @@ main = do unless (bs == res') $ error $ "Unexpected result: " ++ show res' + do -- multithreaded waitForProcess + (_, _, _, p) <- createProcess (proc "sleep" ["0.1"]) + me1 <- newEmptyMVar + forkIO . void $ waitForProcess p >>= putMVar me1 + -- check for race / deadlock between waitForProcess and getProcessExitCode + e3 <- getProcessExitCode p + e2 <- waitForProcess p + e1 <- readMVar me1 + unless (isNothing e3 && e1 == ExitSuccess && e2 == ExitSuccess) + $ error "sleep exited with non-zero exit code!" + putStrLn "Tests passed successfully" withCurrentDirectory :: FilePath -> IO a -> IO a From git at git.haskell.org Wed Jul 19 21:19:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:17 +0000 (UTC) Subject: [commit: packages/process] master: Listen to -Werror (fd79da2) Message-ID: <20170719211917.514903A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fd79da2d7c0f11b4ab70cbd232c2025af43430b5/process >--------------------------------------------------------------- commit fd79da2d7c0f11b4ab70cbd232c2025af43430b5 Author: Charles Cooper Date: Sat Feb 4 15:43:29 2017 -0500 Listen to -Werror >--------------------------------------------------------------- fd79da2d7c0f11b4ab70cbd232c2025af43430b5 test/main.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/test/main.hs b/test/main.hs index f89f3ef..edb561a 100644 --- a/test/main.hs +++ b/test/main.hs @@ -71,12 +71,14 @@ main = do do -- multithreaded waitForProcess (_, _, _, p) <- createProcess (proc "sleep" ["0.1"]) me1 <- newEmptyMVar - forkIO . void $ waitForProcess p >>= putMVar me1 + _ <- forkIO . void $ waitForProcess p >>= putMVar me1 -- check for race / deadlock between waitForProcess and getProcessExitCode e3 <- getProcessExitCode p e2 <- waitForProcess p e1 <- readMVar me1 - unless (isNothing e3 && e1 == ExitSuccess && e2 == ExitSuccess) + unless (isNothing e3) + $ error $ "unexpected exit " ++ show e3 + unless (e1 == ExitSuccess && e2 == ExitSuccess) $ error "sleep exited with non-zero exit code!" putStrLn "Tests passed successfully" From git at git.haskell.org Wed Jul 19 21:19:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:19 +0000 (UTC) Subject: [commit: packages/process] master: Fix warnings (577c22d) Message-ID: <20170719211919.586403A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/577c22dc80f7e3e8cb7fe6bb8392146c6b8341f5/process >--------------------------------------------------------------- commit 577c22dc80f7e3e8cb7fe6bb8392146c6b8341f5 Author: Michael Snoyman Date: Mon Feb 6 10:44:29 2017 +0200 Fix warnings >--------------------------------------------------------------- 577c22dc80f7e3e8cb7fe6bb8392146c6b8341f5 .travis.yml | 2 +- System/Process.hs | 3 ++- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index c045791..04d0bfc 100644 --- a/.travis.yml +++ b/.travis.yml @@ -158,7 +158,7 @@ install: set -ex case "$BUILD" in stack) - stack --no-terminal --install-ghc $ARGS test --bench --only-dependencies + stack --no-terminal --install-ghc $ARGS test --bench --only-dependencies --pedantic ;; cabal) cabal --version diff --git a/System/Process.hs b/System/Process.hs index 81a5788..0112659 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -608,12 +608,13 @@ waitForProcess ph@(ProcessHandle _ delegating_ctlc) = do when delegating_ctlc $ endDelegateControlC e return e - OpenExtHandle _ job iocp -> #if defined(WINDOWS) + OpenExtHandle _ job iocp -> maybe (ExitFailure (-1)) mkExitCode `fmap` waitForJobCompletion job iocp timeout_Infinite where mkExitCode code | code == 0 = ExitSuccess | otherwise = ExitFailure $ fromIntegral code #else + OpenExtHandle _ _job _iocp -> return $ ExitFailure (-1) #endif From git at git.haskell.org Wed Jul 19 21:19:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:21 +0000 (UTC) Subject: [commit: packages/process] master: Update changelog for 1.5.0.0 (fda112a) Message-ID: <20170719211921.5F1553A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fda112ab0ee3ff3289bb2c14ca66540fdb408e73/process >--------------------------------------------------------------- commit fda112ab0ee3ff3289bb2c14ca66540fdb408e73 Author: Michael Snoyman Date: Mon Feb 6 10:51:24 2017 +0200 Update changelog for 1.5.0.0 >--------------------------------------------------------------- fda112ab0ee3ff3289bb2c14ca66540fdb408e73 changelog.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index bee8874..55cbfc6 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,6 @@ # Changelog for [`process` package](http://hackage.haskell.org/package/process) -## Unreleased changes +## 1.5.0.0 *February 2017* * Bug fix: Don't close already closed pipes [#81](https://github.com/haskell/process/pull/81) From git at git.haskell.org Wed Jul 19 21:19:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:23 +0000 (UTC) Subject: [commit: packages/process] master: Add back "Unreleased changes" (e9a201b) Message-ID: <20170719211923.65A0B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e9a201bc48d4ebb5e4d1b731111a764b2a07bbde/process >--------------------------------------------------------------- commit e9a201bc48d4ebb5e4d1b731111a764b2a07bbde Author: Michael Snoyman Date: Mon Feb 6 10:52:09 2017 +0200 Add back "Unreleased changes" >--------------------------------------------------------------- e9a201bc48d4ebb5e4d1b731111a764b2a07bbde changelog.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/changelog.md b/changelog.md index 55cbfc6..bcb4ae5 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,7 @@ # Changelog for [`process` package](http://hackage.haskell.org/package/process) +## Unreleased changes + ## 1.5.0.0 *February 2017* * Bug fix: Don't close already closed pipes From git at git.haskell.org Wed Jul 19 21:19:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:25 +0000 (UTC) Subject: [commit: packages/process] master: Check if waitpidLock is held in getProcessExitCode (c722d8b) Message-ID: <20170719211925.6C91D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c722d8b85568d2185dbe716a9988697eccb27e56/process >--------------------------------------------------------------- commit c722d8b85568d2185dbe716a9988697eccb27e56 Author: Charles Cooper Date: Fri Feb 17 12:03:01 2017 -0800 Check if waitpidLock is held in getProcessExitCode >--------------------------------------------------------------- c722d8b85568d2185dbe716a9988697eccb27e56 System/Process.hs | 21 +++++++++++++++++++-- 1 file changed, 19 insertions(+), 2 deletions(-) diff --git a/System/Process.hs b/System/Process.hs index 50c787e..0a5e93e 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -77,7 +77,7 @@ import System.Process.Internals import Control.Concurrent import Control.DeepSeq (rnf) -import Control.Exception (SomeException, mask, try, throwIO) +import Control.Exception (SomeException, mask, bracket, try, throwIO) import qualified Control.Exception as C import Control.Monad import Data.Maybe @@ -635,7 +635,7 @@ when the process died as the result of a signal. -} getProcessExitCode :: ProcessHandle -> IO (Maybe ExitCode) -getProcessExitCode ph@(ProcessHandle _ delegating_ctlc _) = do +getProcessExitCode ph@(ProcessHandle _ delegating_ctlc _) = tryLockWaitpid $ do (m_e, was_open) <- modifyProcessHandle ph $ \p_ -> case p_ of ClosedHandle e -> return (p_, (Just e, False)) @@ -663,6 +663,23 @@ getProcessExitCode ph@(ProcessHandle _ delegating_ctlc _) = do getHandle (ClosedHandle _) = Nothing getHandle (OpenExtHandle h _ _) = Just h + -- If somebody is currently holding the waitpid lock, we don't want to + -- accidentally remove the pid from the process table. + -- Try acquiring the waitpid lock. If it is held, we are done + -- since that means the process is still running and we can return + -- `Nothing`. If it is not held, acquire it so we can run the + -- (non-blocking) call to `waitpid` without worrying about any + -- other threads calling it at the same time. + tryLockWaitpid :: IO (Maybe ExitCode) -> IO (Maybe ExitCode) + tryLockWaitpid action = bracket acquire release between + where + acquire = tryTakeMVar (waitpidLock ph) + release m = case m of + Nothing -> return () + Just () -> putMVar (waitpidLock ph) () + between m = case m of + Nothing -> return Nothing + Just () -> do action -- ---------------------------------------------------------------------------- -- terminateProcess From git at git.haskell.org Wed Jul 19 21:19:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:27 +0000 (UTC) Subject: [commit: packages/process] master: Remove extra whitespace (48c8fde) Message-ID: <20170719211927.733F93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/48c8fde957e76235224b80149b7f54796c9a6e30/process >--------------------------------------------------------------- commit 48c8fde957e76235224b80149b7f54796c9a6e30 Author: Charles Cooper Date: Mon Feb 20 12:19:36 2017 -0800 Remove extra whitespace >--------------------------------------------------------------- 48c8fde957e76235224b80149b7f54796c9a6e30 System/Process.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Process.hs b/System/Process.hs index 0a5e93e..bc4c1ae 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -679,7 +679,7 @@ getProcessExitCode ph@(ProcessHandle _ delegating_ctlc _) = tryLockWaitpid $ do Just () -> putMVar (waitpidLock ph) () between m = case m of Nothing -> return Nothing - Just () -> do action + Just () -> action -- ---------------------------------------------------------------------------- -- terminateProcess From git at git.haskell.org Wed Jul 19 21:19:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:29 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #58 from charles-cooper/master (3d32c5c) Message-ID: <20170719211929.7A6823A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3d32c5cd9e986fcb6db80d2503e3006c2a33479c/process >--------------------------------------------------------------- commit 3d32c5cd9e986fcb6db80d2503e3006c2a33479c Merge: e9a201b 48c8fde Author: Michael Snoyman Date: Tue Feb 21 15:52:18 2017 +0200 Merge pull request #58 from charles-cooper/master Fix #46 >--------------------------------------------------------------- 3d32c5cd9e986fcb6db80d2503e3006c2a33479c System/Process.hs | 38 ++++++++++++++++++++++++++++++-------- System/Process/Common.hs | 10 +++++++--- System/Process/Posix.hs | 3 ++- System/Process/Windows.hsc | 3 ++- process.cabal | 2 ++ test/main.hs | 17 ++++++++++++++++- 6 files changed, 59 insertions(+), 14 deletions(-) diff --cc System/Process.hs index 0112659,bc4c1ae..8842daa --- a/System/Process.hs +++ b/System/Process.hs @@@ -614,9 -612,15 +612,16 @@@ waitForProcess ph@(ProcessHandle _ dele where mkExitCode code | code == 0 = ExitSuccess | otherwise = ExitFailure $ fromIntegral code #else + OpenExtHandle _ _job _iocp -> return $ ExitFailure (-1) #endif + where + -- If more than one thread calls `waitpid` at a time, `waitpid` will + -- return the exit code to one of them and (-1) to the rest of them, + -- causing an exception to be thrown. + -- Cf. https://github.com/haskell/process/issues/46, and + -- https://github.com/haskell/process/pull/58 for further discussion + lockWaitpid m = withMVar (waitpidLock ph) $ \() -> m -- ---------------------------------------------------------------------------- -- getProcessExitCode From git at git.haskell.org Wed Jul 19 21:19:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:31 +0000 (UTC) Subject: [commit: packages/process] master: Version bump for #46 and #58 (01d517d) Message-ID: <20170719211931.80A5B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/01d517d2557f0abd646ab1a20a932226903c68e1/process >--------------------------------------------------------------- commit 01d517d2557f0abd646ab1a20a932226903c68e1 Author: Michael Snoyman Date: Tue Feb 21 15:54:06 2017 +0200 Version bump for #46 and #58 >--------------------------------------------------------------- 01d517d2557f0abd646ab1a20a932226903c68e1 changelog.md | 4 ++++ process.cabal | 2 +- 2 files changed, 5 insertions(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index bcb4ae5..3084956 100644 --- a/changelog.md +++ b/changelog.md @@ -2,6 +2,10 @@ ## Unreleased changes +* Fix: waitForProcess race condition + [#46](https://github.com/haskell/process/issues/46) + [#58](https://github.com/haskell/process/pull/58) + ## 1.5.0.0 *February 2017* * Bug fix: Don't close already closed pipes diff --git a/process.cabal b/process.cabal index 30d25bb..cfdb867 100644 --- a/process.cabal +++ b/process.cabal @@ -1,5 +1,5 @@ name: process -version: 1.5.0.0 +version: 1.6.0.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE From git at git.haskell.org Wed Jul 19 21:19:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:33 +0000 (UTC) Subject: [commit: packages/process] master: Update ChangeLog for 1.6 release (2edf54b) Message-ID: <20170719211933.86A5D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2edf54b2446581c7d9e9d36446e854b6b6c9223d/process >--------------------------------------------------------------- commit 2edf54b2446581c7d9e9d36446e854b6b6c9223d Author: Michael Snoyman Date: Wed Feb 22 12:13:16 2017 +0200 Update ChangeLog for 1.6 release >--------------------------------------------------------------- 2edf54b2446581c7d9e9d36446e854b6b6c9223d changelog.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index 3084956..cfca120 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,6 @@ # Changelog for [`process` package](http://hackage.haskell.org/package/process) -## Unreleased changes +## 1.6.0.0 *February 2017* * Fix: waitForProcess race condition [#46](https://github.com/haskell/process/issues/46) From git at git.haskell.org Wed Jul 19 21:19:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:37 +0000 (UTC) Subject: [commit: packages/process] master: Include link to typed-process (ad34489) Message-ID: <20170719211937.93DC03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ad344892e2b745458c44ffcb079a52a274f683f2/process >--------------------------------------------------------------- commit ad344892e2b745458c44ffcb079a52a274f683f2 Author: Michael Snoyman Date: Thu Mar 9 11:09:02 2017 +0200 Include link to typed-process >--------------------------------------------------------------- ad344892e2b745458c44ffcb079a52a274f683f2 process.cabal | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/process.cabal b/process.cabal index cfdb867..98516f6 100644 --- a/process.cabal +++ b/process.cabal @@ -11,6 +11,12 @@ build-type: Configure cabal-version: >=1.10 description: This package contains libraries for dealing with system processes. + . + The typed-process package is a more recent take on a process API, + which uses this package internally. It features better binary + support, easier concurrency, and a more composable API. You can + read more about it at + . extra-source-files: aclocal.m4 From git at git.haskell.org Wed Jul 19 21:19:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:35 +0000 (UTC) Subject: [commit: packages/process] master: Add back unreleased changes section (5dba337) Message-ID: <20170719211935.8D5AF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5dba337192180ae4abfda7d25aa0c9d76e40d584/process >--------------------------------------------------------------- commit 5dba337192180ae4abfda7d25aa0c9d76e40d584 Author: Michael Snoyman Date: Wed Feb 22 12:14:40 2017 +0200 Add back unreleased changes section >--------------------------------------------------------------- 5dba337192180ae4abfda7d25aa0c9d76e40d584 changelog.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/changelog.md b/changelog.md index cfca120..98eade5 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,7 @@ # Changelog for [`process` package](http://hackage.haskell.org/package/process) +## Unreleased changes + ## 1.6.0.0 *February 2017* * Fix: waitForProcess race condition From git at git.haskell.org Wed Jul 19 21:19:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:39 +0000 (UTC) Subject: [commit: packages/process] master: AppVeyor: make curl available (6a8cc90) Message-ID: <20170719211939.996873A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6a8cc90e499f12aa621021aea812de7dad27af5b/process >--------------------------------------------------------------- commit 6a8cc90e499f12aa621021aea812de7dad27af5b Author: Michael Snoyman Date: Mon Mar 27 11:29:38 2017 +0300 AppVeyor: make curl available >--------------------------------------------------------------- 6a8cc90e499f12aa621021aea812de7dad27af5b appveyor.yml | 3 +++ 1 file changed, 3 insertions(+) diff --git a/appveyor.yml b/appveyor.yml index 2c313d4..9fbcd3e 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -4,6 +4,9 @@ cache: build: off before_test: +# http://help.appveyor.com/discussions/problems/6312-curl-command-not-found +- set PATH=C:\Program Files\Git\mingw64\bin;%PATH% + - curl -ostack.zip -L --insecure http://www.stackage.org/stack/windows-i386 - 7z x stack.zip stack.exe From git at git.haskell.org Wed Jul 19 21:19:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:41 +0000 (UTC) Subject: [commit: packages/process] master: Fix AppVeyor build by using their msys2 autoreconf (35d8b11) Message-ID: <20170719211941.9F40A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/35d8b11b6cb5884a9917ffe8639dde1450d2d778/process >--------------------------------------------------------------- commit 35d8b11b6cb5884a9917ffe8639dde1450d2d778 Author: Michael Snoyman Date: Mon Mar 27 16:25:56 2017 +0300 Fix AppVeyor build by using their msys2 autoreconf >--------------------------------------------------------------- 35d8b11b6cb5884a9917ffe8639dde1450d2d778 appveyor.yml | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/appveyor.yml b/appveyor.yml index 9fbcd3e..e9f71fe 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -10,14 +10,20 @@ before_test: - curl -ostack.zip -L --insecure http://www.stackage.org/stack/windows-i386 - 7z x stack.zip stack.exe -clone_folder: "c:\\stack" +clone_folder: "c:\\process" environment: global: STACK_ROOT: "c:\\sr" test_script: + +# Generate the configure script. This took way too long to figure out +# correctly. +- c:\msys64\usr\bin\bash -lc "cd /c/process && autoreconf -i" + +# Install toolchain, but do it silently due to lots of output - stack setup > nul + # The ugly echo "" hack is to avoid complaints about 0 being an invalid file # descriptor -- echo y | stack exec -- sh -c "pacman -Sy autoconf perl && autoreconf -i" - echo "" | stack --no-terminal test --pedantic From git at git.haskell.org Wed Jul 19 21:19:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:43 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #92 from haskell/fix-appveyor2 (0159507) Message-ID: <20170719211943.A6E693A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0159507e05147e7eb1fb98b0125ad6cf07cc7e78/process >--------------------------------------------------------------- commit 0159507e05147e7eb1fb98b0125ad6cf07cc7e78 Merge: 6a8cc90 35d8b11 Author: Michael Snoyman Date: Thu Mar 30 18:01:01 2017 +0300 Merge pull request #92 from haskell/fix-appveyor2 Fix AppVeyor build by using their msys2 autoreconf >--------------------------------------------------------------- 0159507e05147e7eb1fb98b0125ad6cf07cc7e78 appveyor.yml | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) From git at git.haskell.org Wed Jul 19 21:19:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:45 +0000 (UTC) Subject: [commit: packages/process] master: Re-export CGid and friends from System.Process.Internals (ce41497) Message-ID: <20170719211945.AD1EF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ce41497d8c325e7dad2abecb28795067f5fd32b6/process >--------------------------------------------------------------- commit ce41497d8c325e7dad2abecb28795067f5fd32b6 Author: Ryan Scott Date: Sat Mar 25 10:31:31 2017 -0400 Re-export CGid and friends from System.Process.Internals >--------------------------------------------------------------- ce41497d8c325e7dad2abecb28795067f5fd32b6 System/Process/Common.hs | 2 ++ System/Process/Internals.hs | 7 +++++++ changelog.md | 4 ++++ 3 files changed, 13 insertions(+) diff --git a/System/Process/Common.hs b/System/Process/Common.hs index dd09c0e..b424764 100644 --- a/System/Process/Common.hs +++ b/System/Process/Common.hs @@ -9,6 +9,8 @@ module System.Process.Common , ProcRetHandles (..) , withFilePathException , PHANDLE + , GroupID + , UserID , modifyProcessHandle , withProcessHandle , fd_stdin diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index 036e1c0..020390e 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -22,6 +22,13 @@ module System.Process.Internals ( ProcessHandle(..), ProcessHandle__(..), PHANDLE, closePHANDLE, mkProcessHandle, +#ifdef WINDOWS + CGid(..), +#else + CGid, +#endif + GroupID, + UserID, modifyProcessHandle, withProcessHandle, CreateProcess(..), CmdSpec(..), StdStream(..), ProcRetHandles (..), diff --git a/changelog.md b/changelog.md index 98eade5..537a744 100644 --- a/changelog.md +++ b/changelog.md @@ -2,6 +2,10 @@ ## Unreleased changes +* Expose `CGid`, `GroupID`, and `UserID` from `System.Process.Internals` + [#90](https://github.com/haskell/process/issues/90) + [#91](https://github.com/haskell/process/pull/91) + ## 1.6.0.0 *February 2017* * Fix: waitForProcess race condition From git at git.haskell.org Wed Jul 19 21:19:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:47 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #91 from RyanGlScott/master (10f31a5) Message-ID: <20170719211947.B3EBE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/10f31a5948de8cf0f697028e877df084005043fa/process >--------------------------------------------------------------- commit 10f31a5948de8cf0f697028e877df084005043fa Merge: 0159507 ce41497 Author: Michael Snoyman Date: Thu Mar 30 20:01:14 2017 +0300 Merge pull request #91 from RyanGlScott/master Re-export CGid and friends from System.Process.Internals >--------------------------------------------------------------- 10f31a5948de8cf0f697028e877df084005043fa System/Process/Common.hs | 2 ++ System/Process/Internals.hs | 7 +++++++ changelog.md | 4 ++++ 3 files changed, 13 insertions(+) From git at git.haskell.org Wed Jul 19 21:19:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:49 +0000 (UTC) Subject: [commit: packages/process] master: Systsem.Process.Posix: Hide mb_delegate_ctlc (eedaff6) Message-ID: <20170719211949.BBE2F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eedaff67abba546360bcff174c2dea58892d1e05/process >--------------------------------------------------------------- commit eedaff67abba546360bcff174c2dea58892d1e05 Author: Ben Gamari Date: Fri Apr 21 19:36:52 2017 -0400 Systsem.Process.Posix: Hide mb_delegate_ctlc As it is shadowed by other local bindings in this module. >--------------------------------------------------------------- eedaff67abba546360bcff174c2dea58892d1e05 System/Process/Posix.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Process/Posix.hs b/System/Process/Posix.hs index 129072f..5432f41 100644 --- a/System/Process/Posix.hs +++ b/System/Process/Posix.hs @@ -40,7 +40,7 @@ import System.Posix.Signals as Sig import qualified System.Posix.IO as Posix import System.Posix.Process (getProcessGroupIDOf) -import System.Process.Common +import System.Process.Common hiding (mb_delegate_ctlc) #include "HsProcessConfig.h" #include "processFlags.h" From git at git.haskell.org Wed Jul 19 21:19:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:19:51 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #94 from bgamari/master (88547b0) Message-ID: <20170719211951.C20EB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/88547b0fae8644f8f69be32c7ee5a3b76051c82f/process >--------------------------------------------------------------- commit 88547b0fae8644f8f69be32c7ee5a3b76051c82f Merge: 10f31a5 eedaff6 Author: Michael Snoyman Date: Sun Apr 23 11:49:22 2017 +0300 Merge pull request #94 from bgamari/master System.Process.Posix: Hide mb_delegate_ctlc >--------------------------------------------------------------- 88547b0fae8644f8f69be32c7ee5a3b76051c82f System/Process/Posix.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Wed Jul 19 21:58:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:58:39 +0000 (UTC) Subject: [commit: packages/deepseq] branch 'down' created Message-ID: <20170719215839.635873A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq New branch : down Referencing: 07922524fbc3b8d220f1cc1b01a3d254d295e910 From git at git.haskell.org Wed Jul 19 21:58:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:58:43 +0000 (UTC) Subject: [commit: packages/deepseq] branch 'travis-tests' created Message-ID: <20170719215843.647603A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq New branch : travis-tests Referencing: 5d88e98b427ef24455e079c96f2124fdd970aa2d From git at git.haskell.org Wed Jul 19 21:58:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:58:45 +0000 (UTC) Subject: [commit: packages/deepseq] branch 'wip/ttypeable' created Message-ID: <20170719215845.6622B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq New branch : wip/ttypeable Referencing: c3a0a16f17e593cb6a64b01a22015497738bfed6 From git at git.haskell.org Wed Jul 19 21:58:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:58:47 +0000 (UTC) Subject: [commit: packages/deepseq] tag 'v1.4.3.0' created Message-ID: <20170719215847.665B43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq New tag : v1.4.3.0 Referencing: 90a373bbb092578e397f792c1d9c5c9a0b4ef030 From git at git.haskell.org Wed Jul 19 21:58:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:58:41 +0000 (UTC) Subject: [commit: packages/deepseq] branch 'wip/remove_ghc70_72_cpp' created Message-ID: <20170719215841.63F0B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq New branch : wip/remove_ghc70_72_cpp Referencing: 4148a11bb470ffe8005b203a2aa40cf087dec210 From git at git.haskell.org Wed Jul 19 21:58:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:58:49 +0000 (UTC) Subject: [commit: packages/deepseq] wip/ttypeable: Update deepseq for type-indexed type representations (c3a0a16) Message-ID: <20170719215849.6D4803A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : wip/ttypeable Link : http://git.haskell.org/packages/deepseq.git/commitdiff/c3a0a16f17e593cb6a64b01a22015497738bfed6 >--------------------------------------------------------------- commit c3a0a16f17e593cb6a64b01a22015497738bfed6 Author: Ben Gamari Date: Wed Mar 16 11:25:11 2016 +0100 Update deepseq for type-indexed type representations >--------------------------------------------------------------- c3a0a16f17e593cb6a64b01a22015497738bfed6 Control/DeepSeq.hs | 29 +++++++++++++++++++++++++++-- 1 file changed, 27 insertions(+), 2 deletions(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 49bac36..4e4379c 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -86,9 +86,14 @@ import Data.Ord ( Down(Down) ) import Data.Proxy ( Proxy(Proxy) ) #endif +#if MIN_VERSION_base(4,9,0) +import Type.Reflection ( TypeRep, TypeRepX, TyCon, rnfTypeRep, rnfTypeRepX, rnfTyCon ) +#elif MIN_VERSION_base(4,8,0) +import Data.Typeable ( TypeRep, TyCon, rnfTypeRep, rnfTyCon ) +#endif + #if MIN_VERSION_base(4,8,0) import Data.Functor.Identity ( Identity(..) ) -import Data.Typeable ( TypeRep, TyCon, rnfTypeRep, rnfTyCon ) import Data.Void ( Void, absurd ) import Numeric.Natural ( Natural ) #endif @@ -406,7 +411,27 @@ instance NFData ThreadId where instance NFData Unique where rnf !_ = () -- assumes `newtype Unique = Unique Integer` -#if MIN_VERSION_base(4,8,0) +#if MIN_VERSION_base(4,9,0) +-- | __NOTE__: Only defined for @base-4.9.0.0@ and later +-- +-- @since 1.4.0.0 +instance NFData (TypeRep a) where + rnf tyrep = rnfTypeRep tyrep + +-- | __NOTE__: Only defined for @base-4.8.0.0@ and later +-- +-- @since 1.4.0.0 +instance NFData TypeRepX where + rnf tyrep = rnfTypeRepX tyrep + +-- | __NOTE__: Only defined for @base-4.8.0.0@ and later +-- +-- @since 1.4.0.0 +instance NFData TyCon where + rnf tycon = rnfTyCon tycon + +#elif MIN_VERSION_base(4,8,0) + -- | __NOTE__: Only defined for @base-4.8.0.0@ and later -- -- @since 1.4.0.0 From git at git.haskell.org Wed Jul 19 21:58:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:58:51 +0000 (UTC) Subject: [commit: packages/deepseq] down, master, travis-tests, wip/remove_ghc70_72_cpp: Fix GNFData instance for V1 (#20) (6ca510a) Message-ID: <20170719215851.731513A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: down,master,travis-tests,wip/remove_ghc70_72_cpp Link : http://git.haskell.org/packages/deepseq.git/commitdiff/6ca510a7d0811dbc163dd9ba32694943f3636c01 >--------------------------------------------------------------- commit 6ca510a7d0811dbc163dd9ba32694943f3636c01 Author: David Feuer Date: Tue Aug 16 08:23:36 2016 -0400 Fix GNFData instance for V1 (#20) Make `grnf` for `V1` a well-defined function that forces its (bottom) argument rather than making the function itself bottom. Fixes #19 >--------------------------------------------------------------- 6ca510a7d0811dbc163dd9ba32694943f3636c01 Control/DeepSeq.hs | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 314d0a9..ca01c53 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -11,6 +11,9 @@ #if __GLASGOW_HASKELL__ >= 706 {-# LANGUAGE PolyKinds #-} #endif +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE EmptyCase #-} +#endif ----------------------------------------------------------------------------- -- | -- Module : Control.DeepSeq @@ -114,7 +117,11 @@ class GNFData f where grnf :: f a -> () instance GNFData V1 where - grnf = error "Control.DeepSeq.rnf: uninhabited type" +#if __GLASGOW_HASKELL__ >= 708 + grnf x = case x of {} +#else + grnf !_ = error "Control.DeepSeq.rnf: uninhabited type" +#endif instance GNFData U1 where grnf U1 = () From git at git.haskell.org Wed Jul 19 21:58:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:58:53 +0000 (UTC) Subject: [commit: packages/deepseq] down, master, travis-tests, wip/remove_ghc70_72_cpp: Minor version bump (9243b9b) Message-ID: <20170719215853.789973A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: down,master,travis-tests,wip/remove_ghc70_72_cpp Link : http://git.haskell.org/packages/deepseq.git/commitdiff/9243b9b8f65f9a46af15ecc167ca9f6b574f6ba5 >--------------------------------------------------------------- commit 9243b9b8f65f9a46af15ecc167ca9f6b574f6ba5 Author: Ryan Scott Date: Tue Aug 16 08:31:28 2016 -0400 Minor version bump >--------------------------------------------------------------- 9243b9b8f65f9a46af15ecc167ca9f6b574f6ba5 changelog.md | 9 +++++++++ deepseq.cabal | 6 +++++- 2 files changed, 14 insertions(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index eb53420..4fad76e 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,14 @@ # Changelog for [`deepseq` package](http://hackage.haskell.org/package/deepseq) +## 1.4.3.0 *TBD* + + * Changed behavior of generic `NFData` instances for constructor-less data + types. Before, a generic `rnf` implementation would always `error` on a + data type with no constructors. Now, it will force the argument, so if + the argument is a diverging computation, a generic `rnf` implementation + will actually trigger the diverging computation. + ([#19](https://github.com/haskell/deepseq/issues/19)) + ## 1.4.2.0 *Apr 2016* * Bundled with GHC 8.0.1 diff --git a/deepseq.cabal b/deepseq.cabal index 0bd8aa9..849c7db 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -1,5 +1,5 @@ name: deepseq -version: 1.4.2.0 +version: 1.4.3.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE @@ -53,6 +53,10 @@ library if impl(ghc < 7.6) build-depends: ghc-prim == 0.2.* + if impl(ghc>=7.8) + other-extensions: + EmptyCase + if impl(ghc < 7.4) build-depends: array < 0.4 From git at git.haskell.org Wed Jul 19 21:58:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:58:57 +0000 (UTC) Subject: [commit: packages/deepseq] travis-tests: Fix .travis.yml syntax (1a20251) Message-ID: <20170719215857.83A333A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : travis-tests Link : http://git.haskell.org/packages/deepseq.git/commitdiff/1a202512e3b825338ffe163a009203b61f569317 >--------------------------------------------------------------- commit 1a202512e3b825338ffe163a009203b61f569317 Author: Ryan Scott Date: Wed Oct 19 19:34:07 2016 -0400 Fix .travis.yml syntax >--------------------------------------------------------------- 1a202512e3b825338ffe163a009203b61f569317 .travis.yml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 90c067f..a1346ab 100644 --- a/.travis.yml +++ b/.travis.yml @@ -85,7 +85,7 @@ install: fi - travis_retry cabal update -v - sed -i 's/^jobs:/-- jobs:/' ${HOME}/.cabal/config - # can't use "cabal install --only-dependencies --enable-tests" due to dep-cycle +# can't use "cabal install --only-dependencies --enable-tests" due to dep-cycle - cabal install 'test-framework == 0.8.*' 'test-framework-hunit == 0.3.*' 'HUnit >= 1.2 && < 1.6' --dry -v > installplan.txt - sed -i -e '1,/^Resolving /d' installplan.txt; cat installplan.txt @@ -100,7 +100,6 @@ install: echo "cabal build-cache MISS"; rm -rf $HOME/.cabsnap; mkdir -p $HOME/.ghc $HOME/.cabal/lib $HOME/.cabal/share $HOME/.cabal/bin; - # can't use "cabal install --only-dependencies --enable-tests" due to dep-cycle cabal install 'test-framework == 0.8.*' 'test-framework-hunit == 0.3.*' 'HUnit >= 1.2 && < 1.6'; fi From git at git.haskell.org Wed Jul 19 21:58:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:58:59 +0000 (UTC) Subject: [commit: packages/deepseq] travis-tests: Fix lingering Travis issues (e8aab28) Message-ID: <20170719215859.8926C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : travis-tests Link : http://git.haskell.org/packages/deepseq.git/commitdiff/e8aab28109a58a5bdb711df7562157b70f28fc98 >--------------------------------------------------------------- commit e8aab28109a58a5bdb711df7562157b70f28fc98 Author: Ryan Scott Date: Wed Oct 19 19:49:10 2016 -0400 Fix lingering Travis issues >--------------------------------------------------------------- e8aab28109a58a5bdb711df7562157b70f28fc98 .travis.yml | 2 +- deepseq.cabal | 1 + 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index a1346ab..2aa11b0 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,6 +1,6 @@ # This file has been generated -- see https://github.com/hvr/multi-ghc-travis language: c -sudo: false +sudo: true cache: directories: diff --git a/deepseq.cabal b/deepseq.cabal index 7590fcd..146e0a2 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -90,6 +90,7 @@ test-suite deepseq-generics-tests build-depends: array, base, + ghc-prim, -- end of packages with inherited version constraints test-framework == 0.8.*, test-framework-hunit == 0.3.*, From git at git.haskell.org Wed Jul 19 21:58:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:58:55 +0000 (UTC) Subject: [commit: packages/deepseq] travis-tests: Run tests on Travis (9a4bed7) Message-ID: <20170719215855.7E4C33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : travis-tests Link : http://git.haskell.org/packages/deepseq.git/commitdiff/9a4bed7191a845ab5397c1f5a2be08914568bf1c >--------------------------------------------------------------- commit 9a4bed7191a845ab5397c1f5a2be08914568bf1c Author: Ryan Scott Date: Wed Oct 19 19:32:10 2016 -0400 Run tests on Travis >--------------------------------------------------------------- 9a4bed7191a845ab5397c1f5a2be08914568bf1c .travis.yml | 9 ++++++--- deepseq.cabal | 2 +- 2 files changed, 7 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 1ff0ad3..90c067f 100644 --- a/.travis.yml +++ b/.travis.yml @@ -85,7 +85,8 @@ install: fi - travis_retry cabal update -v - sed -i 's/^jobs:/-- jobs:/' ${HOME}/.cabal/config - - cabal install --only-dependencies --dry -v > installplan.txt + # can't use "cabal install --only-dependencies --enable-tests" due to dep-cycle + - cabal install 'test-framework == 0.8.*' 'test-framework-hunit == 0.3.*' 'HUnit >= 1.2 && < 1.6' --dry -v > installplan.txt - sed -i -e '1,/^Resolving /d' installplan.txt; cat installplan.txt # check whether current requested install-plan matches cached package-db snapshot @@ -99,7 +100,8 @@ install: echo "cabal build-cache MISS"; rm -rf $HOME/.cabsnap; mkdir -p $HOME/.ghc $HOME/.cabal/lib $HOME/.cabal/share $HOME/.cabal/bin; - cabal install --only-dependencies; + # can't use "cabal install --only-dependencies --enable-tests" due to dep-cycle + cabal install 'test-framework == 0.8.*' 'test-framework-hunit == 0.3.*' 'HUnit >= 1.2 && < 1.6'; fi # snapshot package-db on cache miss @@ -115,9 +117,10 @@ install: # any command which exits with a non-zero exit code causes the build to fail. script: - if [ -f configure.ac ]; then autoreconf -i; fi - - cabal configure -v2 # -v2 provides useful information for debugging + - cabal configure --enable-tests -v2 # -v2 provides useful information for debugging - cabal build # this builds all libraries and executables (including tests/benchmarks) - cabal sdist # tests that a source-distribution can be generated + - cabal test # Check that the resulting source distribution can be built & installed. # If there are no other `.tar.gz` files in `dist`, this can be even simpler: diff --git a/deepseq.cabal b/deepseq.cabal index 849c7db..7590fcd 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -93,4 +93,4 @@ test-suite deepseq-generics-tests -- end of packages with inherited version constraints test-framework == 0.8.*, test-framework-hunit == 0.3.*, - HUnit >= 1.2 && < 1.4 + HUnit >= 1.2 && < 1.6 From git at git.haskell.org Wed Jul 19 21:59:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:01 +0000 (UTC) Subject: [commit: packages/deepseq] travis-tests: Fix lingering Travis issues, pt. 2 (8d952fb) Message-ID: <20170719215901.8EC973A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : travis-tests Link : http://git.haskell.org/packages/deepseq.git/commitdiff/8d952fbfb980085a7f06a507f7aa57a87a8548af >--------------------------------------------------------------- commit 8d952fbfb980085a7f06a507f7aa57a87a8548af Author: Ryan Scott Date: Wed Oct 19 19:50:59 2016 -0400 Fix lingering Travis issues, pt. 2 >--------------------------------------------------------------- 8d952fbfb980085a7f06a507f7aa57a87a8548af .travis.yml | 3 +++ 1 file changed, 3 insertions(+) diff --git a/.travis.yml b/.travis.yml index 2aa11b0..551c359 100644 --- a/.travis.yml +++ b/.travis.yml @@ -83,6 +83,9 @@ install: zcat $HOME/.cabal/packages/hackage.haskell.org/00-index.tar.gz > $HOME/.cabal/packages/hackage.haskell.org/00-index.tar; fi + - if [ "$GHCVER" = "7.2.1" ]; then + sudo /opt/ghc/$GHCVER/bin/ghc-pkg trust base # To avoid a SafeHaskell bug on GHC 7.2.1 + fi - travis_retry cabal update -v - sed -i 's/^jobs:/-- jobs:/' ${HOME}/.cabal/config # can't use "cabal install --only-dependencies --enable-tests" due to dep-cycle From git at git.haskell.org Wed Jul 19 21:59:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:03 +0000 (UTC) Subject: [commit: packages/deepseq] travis-tests: Fix lingering Travis issues, pt. 3 (7cf9eec) Message-ID: <20170719215903.941D23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : travis-tests Link : http://git.haskell.org/packages/deepseq.git/commitdiff/7cf9eecea799e7efcf9517ee347de7a58f538f22 >--------------------------------------------------------------- commit 7cf9eecea799e7efcf9517ee347de7a58f538f22 Author: Ryan Scott Date: Wed Oct 19 19:52:24 2016 -0400 Fix lingering Travis issues, pt. 3 >--------------------------------------------------------------- 7cf9eecea799e7efcf9517ee347de7a58f538f22 .travis.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 551c359..62f4d07 100644 --- a/.travis.yml +++ b/.travis.yml @@ -83,7 +83,8 @@ install: zcat $HOME/.cabal/packages/hackage.haskell.org/00-index.tar.gz > $HOME/.cabal/packages/hackage.haskell.org/00-index.tar; fi - - if [ "$GHCVER" = "7.2.1" ]; then + - if [ "$GHCVER" = "7.2.1" ]; + then sudo /opt/ghc/$GHCVER/bin/ghc-pkg trust base # To avoid a SafeHaskell bug on GHC 7.2.1 fi - travis_retry cabal update -v From git at git.haskell.org Wed Jul 19 21:59:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:05 +0000 (UTC) Subject: [commit: packages/deepseq] travis-tests: Fix lingering Travis issues, pt. 4 (c553bbd) Message-ID: <20170719215905.9A27E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : travis-tests Link : http://git.haskell.org/packages/deepseq.git/commitdiff/c553bbdc385087f0f273fbe905e33950c4500812 >--------------------------------------------------------------- commit c553bbdc385087f0f273fbe905e33950c4500812 Author: Ryan Scott Date: Wed Oct 19 19:53:36 2016 -0400 Fix lingering Travis issues, pt. 4 >--------------------------------------------------------------- c553bbdc385087f0f273fbe905e33950c4500812 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 62f4d07..5c29758 100644 --- a/.travis.yml +++ b/.travis.yml @@ -85,7 +85,7 @@ install: fi - if [ "$GHCVER" = "7.2.1" ]; then - sudo /opt/ghc/$GHCVER/bin/ghc-pkg trust base # To avoid a SafeHaskell bug on GHC 7.2.1 + sudo /opt/ghc/$GHCVER/bin/ghc-pkg trust base; # To avoid a SafeHaskell bug on GHC 7.2.1 fi - travis_retry cabal update -v - sed -i 's/^jobs:/-- jobs:/' ${HOME}/.cabal/config From git at git.haskell.org Wed Jul 19 21:59:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:07 +0000 (UTC) Subject: [commit: packages/deepseq] travis-tests: Fix lingering Travis issues, pt. 5 (5d88e98) Message-ID: <20170719215907.9F9F13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : travis-tests Link : http://git.haskell.org/packages/deepseq.git/commitdiff/5d88e98b427ef24455e079c96f2124fdd970aa2d >--------------------------------------------------------------- commit 5d88e98b427ef24455e079c96f2124fdd970aa2d Author: Ryan Scott Date: Wed Oct 19 19:55:01 2016 -0400 Fix lingering Travis issues, pt. 5 >--------------------------------------------------------------- 5d88e98b427ef24455e079c96f2124fdd970aa2d .travis.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 5c29758..89c8845 100644 --- a/.travis.yml +++ b/.travis.yml @@ -83,9 +83,10 @@ install: zcat $HOME/.cabal/packages/hackage.haskell.org/00-index.tar.gz > $HOME/.cabal/packages/hackage.haskell.org/00-index.tar; fi +# To avoid a SafeHaskell bug on GHC 7.2.1 - if [ "$GHCVER" = "7.2.1" ]; then - sudo /opt/ghc/$GHCVER/bin/ghc-pkg trust base; # To avoid a SafeHaskell bug on GHC 7.2.1 + sudo /opt/ghc/$GHCVER/bin/ghc-pkg trust base; fi - travis_retry cabal update -v - sed -i 's/^jobs:/-- jobs:/' ${HOME}/.cabal/config From git at git.haskell.org Wed Jul 19 21:59:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:11 +0000 (UTC) Subject: [commit: packages/deepseq] down, master, wip/remove_ghc70_72_cpp: Merge pull request #25 from duairc/patch-1 (b0f2bcf) Message-ID: <20170719215911.AB41E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: down,master,wip/remove_ghc70_72_cpp Link : http://git.haskell.org/packages/deepseq.git/commitdiff/b0f2bcf27299bc826959aba7035ebeff09209b41 >--------------------------------------------------------------- commit b0f2bcf27299bc826959aba7035ebeff09209b41 Merge: 9243b9b acfc3e0 Author: Eric Mertens Date: Tue Oct 25 09:20:49 2016 -0700 Merge pull request #25 from duairc/patch-1 Added NFData instance for Ordering >--------------------------------------------------------------- b0f2bcf27299bc826959aba7035ebeff09209b41 Control/DeepSeq.hs | 1 + 1 file changed, 1 insertion(+) From git at git.haskell.org Wed Jul 19 21:59:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:09 +0000 (UTC) Subject: [commit: packages/deepseq] down, master, wip/remove_ghc70_72_cpp: Added NFData instance for Ordering (acfc3e0) Message-ID: <20170719215909.A568E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: down,master,wip/remove_ghc70_72_cpp Link : http://git.haskell.org/packages/deepseq.git/commitdiff/acfc3e091c381e4fec42e7bc1b320a9a7c6f4d8f >--------------------------------------------------------------- commit acfc3e091c381e4fec42e7bc1b320a9a7c6f4d8f Author: Shane Date: Tue Oct 25 11:09:50 2016 +0100 Added NFData instance for Ordering >--------------------------------------------------------------- acfc3e091c381e4fec42e7bc1b320a9a7c6f4d8f Control/DeepSeq.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index ca01c53..4d7e9e6 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -286,6 +286,7 @@ instance NFData Double where rnf !_ = () instance NFData Char where rnf !_ = () instance NFData Bool where rnf !_ = () +instance NFData Ordering where rnf !_ = () instance NFData () where rnf !_ = () instance NFData Int8 where rnf !_ = () From git at git.haskell.org Wed Jul 19 21:59:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:13 +0000 (UTC) Subject: [commit: packages/deepseq] down, master, wip/remove_ghc70_72_cpp: Run tests on Travis (#24) (b01f808) Message-ID: <20170719215913.B006D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: down,master,wip/remove_ghc70_72_cpp Link : http://git.haskell.org/packages/deepseq.git/commitdiff/b01f808ea1b7a7d28ef7f5731396de6b73f5f6e6 >--------------------------------------------------------------- commit b01f808ea1b7a7d28ef7f5731396de6b73f5f6e6 Author: Ryan Scott Date: Tue Oct 25 13:49:58 2016 -0400 Run tests on Travis (#24) (except for GHC < 7.4) >--------------------------------------------------------------- b01f808ea1b7a7d28ef7f5731396de6b73f5f6e6 .travis.yml | 97 +++++++++++++++++++++++++++++++++++------------------------ deepseq.cabal | 3 +- 2 files changed, 60 insertions(+), 40 deletions(-) diff --git a/.travis.yml b/.travis.yml index 1ff0ad3..08f7528 100644 --- a/.travis.yml +++ b/.travis.yml @@ -13,60 +13,60 @@ before_cache: matrix: include: - - env: CABALVER=1.16 GHCVER=7.0.1 + - env: CABALVER=1.24 GHCVER=7.0.1 compiler: ": #GHC 7.0.1" - addons: {apt: {packages: [cabal-install-1.16,ghc-7.0.1], sources: [hvr-ghc]}} - - env: CABALVER=1.16 GHCVER=7.0.2 + addons: {apt: {packages: [cabal-install-1.24,ghc-7.0.1], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=7.0.2 compiler: ": #GHC 7.0.2" - addons: {apt: {packages: [cabal-install-1.16,ghc-7.0.2], sources: [hvr-ghc]}} - - env: CABALVER=1.16 GHCVER=7.0.3 + addons: {apt: {packages: [cabal-install-1.24,ghc-7.0.2], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=7.0.3 compiler: ": #GHC 7.0.3" - addons: {apt: {packages: [cabal-install-1.16,ghc-7.0.3], sources: [hvr-ghc]}} - - env: CABALVER=1.16 GHCVER=7.0.4 + addons: {apt: {packages: [cabal-install-1.24,ghc-7.0.3], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=7.0.4 compiler: ": #GHC 7.0.4" - addons: {apt: {packages: [cabal-install-1.16,ghc-7.0.4], sources: [hvr-ghc]}} - - env: CABALVER=1.16 GHCVER=7.2.1 + addons: {apt: {packages: [cabal-install-1.24,ghc-7.0.4], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=7.2.1 compiler: ": #GHC 7.2.1" - addons: {apt: {packages: [cabal-install-1.16,ghc-7.2.1], sources: [hvr-ghc]}} - - env: CABALVER=1.16 GHCVER=7.2.2 + addons: {apt: {packages: [cabal-install-1.24,ghc-7.2.1], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=7.2.2 compiler: ": #GHC 7.2.2" - addons: {apt: {packages: [cabal-install-1.16,ghc-7.2.2], sources: [hvr-ghc]}} - - env: CABALVER=1.16 GHCVER=7.4.1 + addons: {apt: {packages: [cabal-install-1.24,ghc-7.2.2], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=7.4.1 compiler: ": #GHC 7.4.1" - addons: {apt: {packages: [cabal-install-1.16,ghc-7.4.1], sources: [hvr-ghc]}} - - env: CABALVER=1.16 GHCVER=7.4.2 + addons: {apt: {packages: [cabal-install-1.24,ghc-7.4.1], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=7.4.2 compiler: ": #GHC 7.4.2" - addons: {apt: {packages: [cabal-install-1.16,ghc-7.4.2], sources: [hvr-ghc]}} - - env: CABALVER=1.16 GHCVER=7.6.1 + addons: {apt: {packages: [cabal-install-1.24,ghc-7.4.2], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=7.6.1 compiler: ": #GHC 7.6.1" - addons: {apt: {packages: [cabal-install-1.16,ghc-7.6.1], sources: [hvr-ghc]}} - - env: CABALVER=1.16 GHCVER=7.6.2 + addons: {apt: {packages: [cabal-install-1.24,ghc-7.6.1], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=7.6.2 compiler: ": #GHC 7.6.2" - addons: {apt: {packages: [cabal-install-1.16,ghc-7.6.2], sources: [hvr-ghc]}} - - env: CABALVER=1.16 GHCVER=7.6.3 + addons: {apt: {packages: [cabal-install-1.24,ghc-7.6.2], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=7.6.3 compiler: ": #GHC 7.6.3" - addons: {apt: {packages: [cabal-install-1.16,ghc-7.6.3], sources: [hvr-ghc]}} - - env: CABALVER=1.18 GHCVER=7.8.1 + addons: {apt: {packages: [cabal-install-1.24,ghc-7.6.3], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=7.8.1 compiler: ": #GHC 7.8.1" - addons: {apt: {packages: [cabal-install-1.18,ghc-7.8.1], sources: [hvr-ghc]}} - - env: CABALVER=1.18 GHCVER=7.8.2 + addons: {apt: {packages: [cabal-install-1.24,ghc-7.8.1], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=7.8.2 compiler: ": #GHC 7.8.2" - addons: {apt: {packages: [cabal-install-1.18,ghc-7.8.2], sources: [hvr-ghc]}} - - env: CABALVER=1.18 GHCVER=7.8.3 + addons: {apt: {packages: [cabal-install-1.24,ghc-7.8.2], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=7.8.3 compiler: ": #GHC 7.8.3" - addons: {apt: {packages: [cabal-install-1.18,ghc-7.8.3], sources: [hvr-ghc]}} - - env: CABALVER=1.18 GHCVER=7.8.4 + addons: {apt: {packages: [cabal-install-1.24,ghc-7.8.3], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=7.8.4 compiler: ": #GHC 7.8.4" - addons: {apt: {packages: [cabal-install-1.18,ghc-7.8.4], sources: [hvr-ghc]}} - - env: CABALVER=1.22 GHCVER=7.10.1 + addons: {apt: {packages: [cabal-install-1.24,ghc-7.8.4], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=7.10.1 compiler: ": #GHC 7.10.1" - addons: {apt: {packages: [cabal-install-1.22,ghc-7.10.1], sources: [hvr-ghc]}} - - env: CABALVER=1.22 GHCVER=7.10.2 + addons: {apt: {packages: [cabal-install-1.24,ghc-7.10.1], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=7.10.2 compiler: ": #GHC 7.10.2" - addons: {apt: {packages: [cabal-install-1.22,ghc-7.10.2], sources: [hvr-ghc]}} - - env: CABALVER=1.22 GHCVER=7.10.3 + addons: {apt: {packages: [cabal-install-1.24,ghc-7.10.2], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=7.10.3 compiler: ": #GHC 7.10.3" - addons: {apt: {packages: [cabal-install-1.22,ghc-7.10.3], sources: [hvr-ghc]}} + addons: {apt: {packages: [cabal-install-1.24,ghc-7.10.3], sources: [hvr-ghc]}} - env: CABALVER=1.24 GHCVER=8.0.1 compiler: ": #GHC 8.0.1" addons: {apt: {packages: [cabal-install-1.24,ghc-8.0.1], sources: [hvr-ghc]}} @@ -74,6 +74,10 @@ matrix: before_install: - unset CC - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH + - if [ "$GHCVER" != "7.2.1" ]; + then + export TEST_OPTS="--enable-tests --enable-benchmarks"; + fi install: - cabal --version @@ -85,7 +89,13 @@ install: fi - travis_retry cabal update -v - sed -i 's/^jobs:/-- jobs:/' ${HOME}/.cabal/config - - cabal install --only-dependencies --dry -v > installplan.txt +# can't use "cabal install --only-dependencies --enable-tests" due to dep-cycle + - if [ -n "$TEST_OPTS" ]; + then + cabal install 'test-framework == 0.8.*' 'test-framework-hunit == 0.3.*' 'HUnit >= 1.2 && < 1.6' --dry -v > installplan.txt; + else + cabal install --only-dependencies --dry -v > installplan.txt; + fi - sed -i -e '1,/^Resolving /d' installplan.txt; cat installplan.txt # check whether current requested install-plan matches cached package-db snapshot @@ -99,7 +109,12 @@ install: echo "cabal build-cache MISS"; rm -rf $HOME/.cabsnap; mkdir -p $HOME/.ghc $HOME/.cabal/lib $HOME/.cabal/share $HOME/.cabal/bin; - cabal install --only-dependencies; + if [ -n "$TEST_OPTS" ]; + then + cabal install -j 'test-framework == 0.8.*' 'test-framework-hunit == 0.3.*' 'HUnit >= 1.2 && < 1.6'; + else + cabal install -j --only-dependencies; + fi fi # snapshot package-db on cache miss @@ -115,9 +130,13 @@ install: # any command which exits with a non-zero exit code causes the build to fail. script: - if [ -f configure.ac ]; then autoreconf -i; fi - - cabal configure -v2 # -v2 provides useful information for debugging + - cabal configure $TEST_OPTS -v2 # -v2 provides useful information for debugging - cabal build # this builds all libraries and executables (including tests/benchmarks) - cabal sdist # tests that a source-distribution can be generated + - if [ -n "$TEST_OPTS" ]; + then + cabal test --show-details=always; + fi # Check that the resulting source distribution can be built & installed. # If there are no other `.tar.gz` files in `dist`, this can be even simpler: diff --git a/deepseq.cabal b/deepseq.cabal index 849c7db..146e0a2 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -90,7 +90,8 @@ test-suite deepseq-generics-tests build-depends: array, base, + ghc-prim, -- end of packages with inherited version constraints test-framework == 0.8.*, test-framework-hunit == 0.3.*, - HUnit >= 1.2 && < 1.4 + HUnit >= 1.2 && < 1.6 From git at git.haskell.org Wed Jul 19 21:59:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:15 +0000 (UTC) Subject: [commit: packages/deepseq] down, master, wip/remove_ghc70_72_cpp: Bump upper bound on deepseq (fe59233) Message-ID: <20170719215915.B567D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: down,master,wip/remove_ghc70_72_cpp Link : http://git.haskell.org/packages/deepseq.git/commitdiff/fe592334abce7ada36ef43f9bfa5f9528b51747d >--------------------------------------------------------------- commit fe592334abce7ada36ef43f9bfa5f9528b51747d Author: Ben Gamari Date: Tue Nov 15 12:51:47 2016 -0500 Bump upper bound on deepseq >--------------------------------------------------------------- fe592334abce7ada36ef43f9bfa5f9528b51747d deepseq.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/deepseq.cabal b/deepseq.cabal index 146e0a2..95a16a3 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -60,7 +60,7 @@ library if impl(ghc < 7.4) build-depends: array < 0.4 - build-depends: base >= 4.3 && < 4.10, + build-depends: base >= 4.3 && < 4.11, array >= 0.3 && < 0.6 ghc-options: -Wall From git at git.haskell.org Wed Jul 19 21:59:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:19 +0000 (UTC) Subject: [commit: packages/deepseq] down, master, wip/remove_ghc70_72_cpp: Add rwhnf (#22) (d496ce4) Message-ID: <20170719215919.C0FB13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: down,master,wip/remove_ghc70_72_cpp Link : http://git.haskell.org/packages/deepseq.git/commitdiff/d496ce4ca1a1141dda3fe90b129d842e7c52c7e4 >--------------------------------------------------------------- commit d496ce4ca1a1141dda3fe90b129d842e7c52c7e4 Author: Oleg Grenrus Date: Thu Nov 17 21:26:48 2016 +0200 Add rwhnf (#22) >--------------------------------------------------------------- d496ce4ca1a1141dda3fe90b129d842e7c52c7e4 Control/DeepSeq.hs | 132 ++++++++++++++++++++++++++++++----------------------- 1 file changed, 75 insertions(+), 57 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 d496ce4ca1a1141dda3fe90b129d842e7c52c7e4 From git at git.haskell.org Wed Jul 19 21:59:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:17 +0000 (UTC) Subject: [commit: packages/deepseq] down, master, wip/remove_ghc70_72_cpp: Add strict liftM (#23) (e01ad84) Message-ID: <20170719215917.BA5D83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: down,master,wip/remove_ghc70_72_cpp Link : http://git.haskell.org/packages/deepseq.git/commitdiff/e01ad84372221ac0d7088c674344acec4b7deb1d >--------------------------------------------------------------- commit e01ad84372221ac0d7088c674344acec4b7deb1d Author: Oleg Grenrus Date: Thu Nov 17 16:39:14 2016 +0200 Add strict liftM (#23) >--------------------------------------------------------------- e01ad84372221ac0d7088c674344acec4b7deb1d Control/DeepSeq.hs | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 4d7e9e6..384a036 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -59,7 +59,7 @@ -- -- @since 1.1.0.0 module Control.DeepSeq ( - deepseq, ($!!), force, + deepseq, ($!!), force, (<$!!>), NFData(..), ) where @@ -209,6 +209,13 @@ f $!! x = x `deepseq` f x force :: (NFData a) => a -> a force x = x `deepseq` x +-- | Deeply strict version of 'Control.Applicative.<$>'. +-- +-- @since 1.4.3.0 +(<$!!>) :: (Monad m, NFData b) => (a -> b) -> m a -> m b +f <$!!> m = m >>= \x -> return $!! f x +infixl 4 <$!!> + -- | A class of types that can be fully evaluated. -- -- @since 1.1.0.0 From git at git.haskell.org Wed Jul 19 21:59:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:21 +0000 (UTC) Subject: [commit: packages/deepseq] down, master, wip/remove_ghc70_72_cpp: Add NFData1 and NFData2 classes (#21) (418856a) Message-ID: <20170719215921.C89853A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: down,master,wip/remove_ghc70_72_cpp Link : http://git.haskell.org/packages/deepseq.git/commitdiff/418856afb4e70127d9dce309a198b18dc47bd7d9 >--------------------------------------------------------------- commit 418856afb4e70127d9dce309a198b18dc47bd7d9 Author: Oleg Grenrus Date: Sun Nov 20 21:10:07 2016 +0200 Add NFData1 and NFData2 classes (#21) * Add NFData1 and NFData2 classes * Add Changelog entries * Add Changelog for NFData1/2 * Generate tuple instances for NFData1/2 * Add NFData1 Fixed and Ratio * Generic NFData1 * Add NFData1 generic deriving docs * Add |@since 1.4.3.0 * Add NFData1/2 Array instances * *Var/*Ptr NFData1 instances >--------------------------------------------------------------- 418856afb4e70127d9dce309a198b18dc47bd7d9 Control/DeepSeq.hs | 415 +++++++++++++++++++++++++++++++++-------------- changelog.md | 5 + deepseq.cabal | 3 + generate-nfdata-tuple.hs | 33 ++++ tests/Main.hs | 41 ++++- 5 files changed, 371 insertions(+), 126 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 418856afb4e70127d9dce309a198b18dc47bd7d9 From git at git.haskell.org Wed Jul 19 21:59:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:23 +0000 (UTC) Subject: [commit: packages/deepseq] down, master: Expose NFData instance for Down on earlier versions of base (0792252) Message-ID: <20170719215923.CEBFF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: down,master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/07922524fbc3b8d220f1cc1b01a3d254d295e910 >--------------------------------------------------------------- commit 07922524fbc3b8d220f1cc1b01a3d254d295e910 Author: Ryan Scott Date: Mon Dec 12 15:22:10 2016 -0500 Expose NFData instance for Down on earlier versions of base >--------------------------------------------------------------- 07922524fbc3b8d220f1cc1b01a3d254d295e910 Control/DeepSeq.hs | 4 ++-- changelog.md | 1 + 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 29c3dc1..875c3b1 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -88,6 +88,8 @@ import System.Mem.StableName ( StableName ) #if MIN_VERSION_base(4,6,0) import Data.Ord ( Down(Down) ) +#else +import GHC.Exts ( Down(Down) ) #endif #if MIN_VERSION_base(4,7,0) @@ -507,13 +509,11 @@ instance NFData2 Array where liftRnf2 r r' x = liftRnf2 r r (bounds x) `seq` liftRnf r' (Data.Array.elems x) #endif -#if MIN_VERSION_base(4,6,0) -- |@since 1.4.0.0 instance NFData a => NFData (Down a) where rnf = rnf1 -- |@since 1.4.3.0 instance NFData1 Down where liftRnf r (Down x) = r x -#endif -- |@since 1.4.0.0 instance NFData a => NFData (Dual a) where rnf = rnf1 diff --git a/changelog.md b/changelog.md index 3a171cf..dc66b87 100644 --- a/changelog.md +++ b/changelog.md @@ -13,6 +13,7 @@ ([#13](https://github.com/haskell/deepseq/issues/13)) * Add `NFData Ordering` ([#25](https://github.com/haskell/deepseq/pull/25)) * Add `NFData1` and `NFData2` type classes ([#8](https://github.com/haskell/deepseq/issues/8)) + * Expose `NFData` instance for `Down` on earlier versions of `base` ## 1.4.2.0 *Apr 2016* From git at git.haskell.org Wed Jul 19 21:59:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:25 +0000 (UTC) Subject: [commit: packages/deepseq] master, wip/remove_ghc70_72_cpp: Add NFData and NFData1 instances for Compose (e0f40eb) Message-ID: <20170719215925.D588A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,wip/remove_ghc70_72_cpp Link : http://git.haskell.org/packages/deepseq.git/commitdiff/e0f40eb3eba22b7c363380931db16cb9e40ffc90 >--------------------------------------------------------------- commit e0f40eb3eba22b7c363380931db16cb9e40ffc90 Author: Pepe Iborra Date: Mon Feb 27 20:44:12 2017 +0000 Add NFData and NFData1 instances for Compose >--------------------------------------------------------------- e0f40eb3eba22b7c363380931db16cb9e40ffc90 Control/DeepSeq.hs | 8 ++++++++ changelog.md | 1 + 2 files changed, 9 insertions(+) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 29c3dc1..ca36cae 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -108,6 +108,7 @@ import Data.Semigroup as Semi #if MIN_VERSION_base(4,9,0) import GHC.Stack.Types ( CallStack(..), SrcLoc(..) ) +import Data.Functor.Compose #elif MIN_VERSION_base(4,8,1) import GHC.Stack ( CallStack(..) ) import GHC.SrcLoc ( SrcLoc(..) ) @@ -426,7 +427,14 @@ instance NFData (a -> b) where rnf = rwhnf instance NFData1 Ratio where liftRnf r x = r (numerator x) `seq` r (denominator x) +-- | @since 1.4.3.0 +instance (NFData1 f, NFData1 g) => NFData1(Compose f g) where liftRnf r = liftRnf (liftRnf r) . getCompose + +-- | @since 1.4.3.0 +instance (NFData1 f, NFData1 g, NFData a) => NFData (Compose f g a) where rnf = rnf1 + instance NFData a => NFData (Ratio a) where + #else instance (Integral a, NFData a) => NFData (Ratio a) where #endif diff --git a/changelog.md b/changelog.md index 3a171cf..0a9380d 100644 --- a/changelog.md +++ b/changelog.md @@ -13,6 +13,7 @@ ([#13](https://github.com/haskell/deepseq/issues/13)) * Add `NFData Ordering` ([#25](https://github.com/haskell/deepseq/pull/25)) * Add `NFData1` and `NFData2` type classes ([#8](https://github.com/haskell/deepseq/issues/8)) + * Add `NFData1` and `NFData` instances for Compose ## 1.4.2.0 *Apr 2016* From git at git.haskell.org Wed Jul 19 21:59:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:27 +0000 (UTC) Subject: [commit: packages/deepseq] master, wip/remove_ghc70_72_cpp: Add NFData instances for Functor Sum and Product (7ef5f11) Message-ID: <20170719215927.DABD73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,wip/remove_ghc70_72_cpp Link : http://git.haskell.org/packages/deepseq.git/commitdiff/7ef5f110ac77c20f0de157ef210bb87d62c80807 >--------------------------------------------------------------- commit 7ef5f110ac77c20f0de157ef210bb87d62c80807 Author: Pepe Iborra Date: Sat Apr 8 10:29:33 2017 +0100 Add NFData instances for Functor Sum and Product >--------------------------------------------------------------- 7ef5f110ac77c20f0de157ef210bb87d62c80807 Control/DeepSeq.hs | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index ca36cae..344991d 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -109,6 +109,8 @@ import Data.Semigroup as Semi #if MIN_VERSION_base(4,9,0) import GHC.Stack.Types ( CallStack(..), SrcLoc(..) ) import Data.Functor.Compose +import qualified Data.Functor.Sum as Functor +import qualified Data.Functor.Product as Functor #elif MIN_VERSION_base(4,8,1) import GHC.Stack ( CallStack(..) ) import GHC.SrcLoc ( SrcLoc(..) ) @@ -433,6 +435,21 @@ instance (NFData1 f, NFData1 g) => NFData1(Compose f g) where liftRnf r = liftRn -- | @since 1.4.3.0 instance (NFData1 f, NFData1 g, NFData a) => NFData (Compose f g a) where rnf = rnf1 +-- | @since 1.4.3.0 +instance (NFData1 f, NFData1 g) => NFData1(Functor.Sum f g) where + liftRnf rnf0 (Functor.InL l) = liftRnf rnf0 l + liftRnf rnf0 (Functor.InR r) = liftRnf rnf0 r + +-- | @since 1.4.3.0 +instance (NFData1 f, NFData1 g, NFData a) => NFData(Functor.Sum f g a) where rnf = rnf1 + +-- | @since 1.4.3.0 +instance (NFData1 f, NFData1 g) => NFData1(Functor.Product f g) where + liftRnf rnf0 (Functor.Pair f g) = liftRnf rnf0 f `seq` liftRnf rnf0 g + +-- | @since 1.4.3.0 +instance (NFData1 f, NFData1 g, NFData a) => NFData(Functor.Product f g a) where rnf = rnf1 + instance NFData a => NFData (Ratio a) where #else From git at git.haskell.org Wed Jul 19 21:59:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:29 +0000 (UTC) Subject: [commit: packages/deepseq] master, wip/remove_ghc70_72_cpp: Update CHANGELOG for #30 (a201067) Message-ID: <20170719215929.E087B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,wip/remove_ghc70_72_cpp Link : http://git.haskell.org/packages/deepseq.git/commitdiff/a2010677bd7019001acccbc52739320050fa2dda >--------------------------------------------------------------- commit a2010677bd7019001acccbc52739320050fa2dda Author: Ryan Scott Date: Sat Apr 8 13:17:42 2017 -0400 Update CHANGELOG for #30 Plus some minor code cleanup >--------------------------------------------------------------- a2010677bd7019001acccbc52739320050fa2dda Control/DeepSeq.hs | 17 ++++++++++------- changelog.md | 3 ++- 2 files changed, 12 insertions(+), 8 deletions(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 344991d..4c5505e 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -430,28 +430,31 @@ instance NFData1 Ratio where liftRnf r x = r (numerator x) `seq` r (denominator x) -- | @since 1.4.3.0 -instance (NFData1 f, NFData1 g) => NFData1(Compose f g) where liftRnf r = liftRnf (liftRnf r) . getCompose +instance (NFData1 f, NFData1 g) => NFData1 (Compose f g) where + liftRnf r = liftRnf (liftRnf r) . getCompose -- | @since 1.4.3.0 -instance (NFData1 f, NFData1 g, NFData a) => NFData (Compose f g a) where rnf = rnf1 +instance (NFData1 f, NFData1 g, NFData a) => NFData (Compose f g a) where + rnf = rnf1 -- | @since 1.4.3.0 -instance (NFData1 f, NFData1 g) => NFData1(Functor.Sum f g) where +instance (NFData1 f, NFData1 g) => NFData1 (Functor.Sum f g) where liftRnf rnf0 (Functor.InL l) = liftRnf rnf0 l liftRnf rnf0 (Functor.InR r) = liftRnf rnf0 r -- | @since 1.4.3.0 -instance (NFData1 f, NFData1 g, NFData a) => NFData(Functor.Sum f g a) where rnf = rnf1 +instance (NFData1 f, NFData1 g, NFData a) => NFData (Functor.Sum f g a) where + rnf = rnf1 -- | @since 1.4.3.0 -instance (NFData1 f, NFData1 g) => NFData1(Functor.Product f g) where +instance (NFData1 f, NFData1 g) => NFData1 (Functor.Product f g) where liftRnf rnf0 (Functor.Pair f g) = liftRnf rnf0 f `seq` liftRnf rnf0 g -- | @since 1.4.3.0 -instance (NFData1 f, NFData1 g, NFData a) => NFData(Functor.Product f g a) where rnf = rnf1 +instance (NFData1 f, NFData1 g, NFData a) => NFData (Functor.Product f g a) where + rnf = rnf1 instance NFData a => NFData (Ratio a) where - #else instance (Integral a, NFData a) => NFData (Ratio a) where #endif diff --git a/changelog.md b/changelog.md index 0a9380d..8f95f22 100644 --- a/changelog.md +++ b/changelog.md @@ -13,7 +13,8 @@ ([#13](https://github.com/haskell/deepseq/issues/13)) * Add `NFData Ordering` ([#25](https://github.com/haskell/deepseq/pull/25)) * Add `NFData1` and `NFData2` type classes ([#8](https://github.com/haskell/deepseq/issues/8)) - * Add `NFData1` and `NFData` instances for Compose + * Add `NFData1` and `NFData` instances for `Data.Functor.{Compose,Sum,Product}` + ([#30](https://github.com/haskell/deepseq/pull/30)) ## 1.4.2.0 *Apr 2016* From git at git.haskell.org Wed Jul 19 21:59:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:31 +0000 (UTC) Subject: [commit: packages/deepseq] master, wip/remove_ghc70_72_cpp: Merge branch 'pepeiborra-master' (4353e0c) Message-ID: <20170719215931.E60343A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,wip/remove_ghc70_72_cpp Link : http://git.haskell.org/packages/deepseq.git/commitdiff/4353e0c47dbd35256491c773b55619cca9fab8ab >--------------------------------------------------------------- commit 4353e0c47dbd35256491c773b55619cca9fab8ab Merge: 418856a a201067 Author: Ryan Scott Date: Sat Apr 8 13:18:03 2017 -0400 Merge branch 'pepeiborra-master' >--------------------------------------------------------------- 4353e0c47dbd35256491c773b55619cca9fab8ab Control/DeepSeq.hs | 28 ++++++++++++++++++++++++++++ changelog.md | 2 ++ 2 files changed, 30 insertions(+) From git at git.haskell.org Wed Jul 19 21:59:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:35 +0000 (UTC) Subject: [commit: packages/deepseq] master, wip/remove_ghc70_72_cpp: Add GHC 8.0.2 to Travis builds (c8c0e51) Message-ID: <20170719215935.F0AB73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,wip/remove_ghc70_72_cpp Link : http://git.haskell.org/packages/deepseq.git/commitdiff/c8c0e51e9669032c1fcef68d5755759dcb22b4e5 >--------------------------------------------------------------- commit c8c0e51e9669032c1fcef68d5755759dcb22b4e5 Author: Ryan Scott Date: Sat Apr 8 13:24:36 2017 -0400 Add GHC 8.0.2 to Travis builds >--------------------------------------------------------------- c8c0e51e9669032c1fcef68d5755759dcb22b4e5 .travis.yml | 3 +++ 1 file changed, 3 insertions(+) diff --git a/.travis.yml b/.travis.yml index 08f7528..bdcaaaf 100644 --- a/.travis.yml +++ b/.travis.yml @@ -70,6 +70,9 @@ matrix: - env: CABALVER=1.24 GHCVER=8.0.1 compiler: ": #GHC 8.0.1" addons: {apt: {packages: [cabal-install-1.24,ghc-8.0.1], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=8.0.2 + compiler: ": #GHC 8.0.2" + addons: {apt: {packages: [cabal-install-1.24,ghc-8.0.2], sources: [hvr-ghc]}} before_install: - unset CC From git at git.haskell.org Wed Jul 19 21:59:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:33 +0000 (UTC) Subject: [commit: packages/deepseq] master, wip/remove_ghc70_72_cpp: Bump HUnit upper version bounds (034f5e3) Message-ID: <20170719215933.EB8213A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,wip/remove_ghc70_72_cpp Link : http://git.haskell.org/packages/deepseq.git/commitdiff/034f5e308bc6cbeaff1b4d62830a6d08daa011e9 >--------------------------------------------------------------- commit 034f5e308bc6cbeaff1b4d62830a6d08daa011e9 Author: Ryan Scott Date: Sat Apr 8 13:22:03 2017 -0400 Bump HUnit upper version bounds >--------------------------------------------------------------- 034f5e308bc6cbeaff1b4d62830a6d08daa011e9 deepseq.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/deepseq.cabal b/deepseq.cabal index 83ff9cf..1883377 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -97,4 +97,4 @@ test-suite deepseq-generics-tests -- end of packages with inherited version constraints test-framework == 0.8.*, test-framework-hunit == 0.3.*, - HUnit >= 1.2 && < 1.6 + HUnit >= 1.2 && < 1.7 From git at git.haskell.org Wed Jul 19 21:59:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:38 +0000 (UTC) Subject: [commit: packages/deepseq] master: Add NFData{1, 2} instances for (:~:) and (:~~:) (af54b3e) Message-ID: <20170719215938.029293A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/af54b3e2e91e02db9206dc8433a8b81cb111e35f >--------------------------------------------------------------- commit af54b3e2e91e02db9206dc8433a8b81cb111e35f Author: Ryan Scott Date: Sat Apr 8 13:56:44 2017 -0400 Add NFData{1,2} instances for (:~:) and (:~~:) >--------------------------------------------------------------- af54b3e2e91e02db9206dc8433a8b81cb111e35f Control/DeepSeq.hs | 17 +++++++++++++++++ changelog.md | 2 ++ 2 files changed, 19 insertions(+) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 4c5505e..26167af 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -92,6 +92,7 @@ import Data.Ord ( Down(Down) ) #if MIN_VERSION_base(4,7,0) import Data.Proxy ( Proxy(Proxy) ) +import Data.Type.Equality #endif #if MIN_VERSION_base(4,8,0) @@ -388,6 +389,22 @@ instance NFData Word64 where rnf = rwhnf instance NFData (Proxy a) where rnf Proxy = () -- |@since 1.4.3.0 instance NFData1 Proxy where liftRnf _ Proxy = () + +-- | @since 1.4.3.0 +instance NFData (a :~: b) where rnf = rwhnf +-- | @since 1.4.3.0 +instance NFData1 ((:~:) a) where liftRnf _ = rwhnf +-- | @since 1.4.3.0 +instance NFData2 (:~:) where liftRnf2 _ _ = rwhnf +#endif + +#if MIN_VERSION_base(4,10,0) +-- | @since 1.4.3.0 +instance NFData (a :~~: b) where rnf = rwhnf +-- | @since 1.4.3.0 +instance NFData1 ((:~~:) a) where liftRnf _ = rwhnf +-- | @since 1.4.3.0 +instance NFData2 (:~~:) where liftRnf2 _ _ = rwhnf #endif #if MIN_VERSION_base(4,8,0) diff --git a/changelog.md b/changelog.md index 8f95f22..fef1ead 100644 --- a/changelog.md +++ b/changelog.md @@ -15,6 +15,8 @@ * Add `NFData1` and `NFData2` type classes ([#8](https://github.com/haskell/deepseq/issues/8)) * Add `NFData1` and `NFData` instances for `Data.Functor.{Compose,Sum,Product}` ([#30](https://github.com/haskell/deepseq/pull/30)) + * Add `NFData`, `NFData1`, and `NFData2` instances for `(:~:)` and `(:~~:)` + from `Data.Type.Equality` ([#31](https://github.com/haskell/deepseq/issues/31)) ## 1.4.2.0 *Apr 2016* From git at git.haskell.org Wed Jul 19 21:59:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:40 +0000 (UTC) Subject: [commit: packages/deepseq] wip/remove_ghc70_72_cpp: Drop support and CPP for GHC 7.0 & GHC 7.2 (4148a11) Message-ID: <20170719215940.08DEC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : wip/remove_ghc70_72_cpp Link : http://git.haskell.org/packages/deepseq.git/commitdiff/4148a11bb470ffe8005b203a2aa40cf087dec210 >--------------------------------------------------------------- commit 4148a11bb470ffe8005b203a2aa40cf087dec210 Author: Herbert Valerio Riedel Date: Sun Apr 16 01:30:34 2017 +0200 Drop support and CPP for GHC 7.0 & GHC 7.2 >--------------------------------------------------------------- 4148a11bb470ffe8005b203a2aa40cf087dec210 .travis.yml | 26 ++++---------------------- Control/DeepSeq.hs | 24 ++++-------------------- changelog.md | 1 + deepseq.cabal | 43 ++++++++++++++++++++----------------------- 4 files changed, 29 insertions(+), 65 deletions(-) diff --git a/.travis.yml b/.travis.yml index bdcaaaf..31ade0e 100644 --- a/.travis.yml +++ b/.travis.yml @@ -13,24 +13,6 @@ before_cache: matrix: include: - - env: CABALVER=1.24 GHCVER=7.0.1 - compiler: ": #GHC 7.0.1" - addons: {apt: {packages: [cabal-install-1.24,ghc-7.0.1], sources: [hvr-ghc]}} - - env: CABALVER=1.24 GHCVER=7.0.2 - compiler: ": #GHC 7.0.2" - addons: {apt: {packages: [cabal-install-1.24,ghc-7.0.2], sources: [hvr-ghc]}} - - env: CABALVER=1.24 GHCVER=7.0.3 - compiler: ": #GHC 7.0.3" - addons: {apt: {packages: [cabal-install-1.24,ghc-7.0.3], sources: [hvr-ghc]}} - - env: CABALVER=1.24 GHCVER=7.0.4 - compiler: ": #GHC 7.0.4" - addons: {apt: {packages: [cabal-install-1.24,ghc-7.0.4], sources: [hvr-ghc]}} - - env: CABALVER=1.24 GHCVER=7.2.1 - compiler: ": #GHC 7.2.1" - addons: {apt: {packages: [cabal-install-1.24,ghc-7.2.1], sources: [hvr-ghc]}} - - env: CABALVER=1.24 GHCVER=7.2.2 - compiler: ": #GHC 7.2.2" - addons: {apt: {packages: [cabal-install-1.24,ghc-7.2.2], sources: [hvr-ghc]}} - env: CABALVER=1.24 GHCVER=7.4.1 compiler: ": #GHC 7.4.1" addons: {apt: {packages: [cabal-install-1.24,ghc-7.4.1], sources: [hvr-ghc]}} @@ -73,14 +55,14 @@ matrix: - env: CABALVER=1.24 GHCVER=8.0.2 compiler: ": #GHC 8.0.2" addons: {apt: {packages: [cabal-install-1.24,ghc-8.0.2], sources: [hvr-ghc]}} + - env: CABALVER=2.0 GHCVER=8.2.1 + compiler: ": #GHC 8.2.1" + addons: {apt: {packages: [cabal-install-2.0,ghc-8.2.1], sources: [hvr-ghc]}} before_install: - unset CC - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH - - if [ "$GHCVER" != "7.2.1" ]; - then - export TEST_OPTS="--enable-tests --enable-benchmarks"; - fi + - export TEST_OPTS="--enable-tests --enable-benchmarks"; install: - cabal --version diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 4c5505e..093056b 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -1,22 +1,21 @@ {-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} -#if __GLASGOW_HASKELL__ >= 702 {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} -{-# LANGUAGE TypeOperators #-} -# if MIN_VERSION_array(0,4,0) {-# LANGUAGE Safe #-} -# endif -#endif +{-# LANGUAGE TypeOperators #-} + #if __GLASGOW_HASKELL__ >= 706 {-# LANGUAGE PolyKinds #-} #endif + #if __GLASGOW_HASKELL__ >= 708 {-# LANGUAGE EmptyCase #-} #endif + ----------------------------------------------------------------------------- -- | -- Module : Control.DeepSeq @@ -116,7 +115,6 @@ import GHC.Stack ( CallStack(..) ) import GHC.SrcLoc ( SrcLoc(..) ) #endif -#if __GLASGOW_HASKELL__ >= 702 import GHC.Fingerprint.Type ( Fingerprint(..) ) import GHC.Generics @@ -166,7 +164,6 @@ instance NFData1 f => GNFData One (Rec1 f) where instance (NFData1 f, GNFData One g) => GNFData One (f :.: g) where grnf args = liftRnf (grnf args) . unComp1 -#endif infixr 0 $!! @@ -325,11 +322,8 @@ class NFData a where -- rnf :: a -> () -#if __GLASGOW_HASKELL__ >= 702 default rnf :: (Generic a, GNFData Zero (Rep a)) => a -> () rnf = grnf RnfArgs0 . from -#endif - -- | A class of functors that can be fully evaluated. -- @@ -342,10 +336,8 @@ class NFData1 f where -- See 'rnf' for the generic deriving. liftRnf :: (a -> ()) -> f a -> () -#if __GLASGOW_HASKELL__ >= 702 default liftRnf :: (Generic1 f, GNFData One (Rep1 f)) => (a -> ()) -> f a -> () liftRnf r = grnf (RnfArgs1 r) . from1 -#endif -- |@since 1.4.3.0 rnf1 :: (NFData1 f, NFData a) => f a -> () @@ -460,11 +452,7 @@ instance (Integral a, NFData a) => NFData (Ratio a) where #endif rnf x = rnf (numerator x, denominator x) -#if MIN_VERSION_base(4,4,0) instance (NFData a) => NFData (Complex a) where -#else -instance (RealFloat a, NFData a) => NFData (Complex a) where -#endif rnf (x:+y) = rnf x `seq` rnf y `seq` () @@ -641,11 +629,9 @@ instance NFData1 MVar where ---------------------------------------------------------------------------- -- GHC Specifics -#if __GLASGOW_HASKELL__ >= 702 -- |@since 1.4.0.0 instance NFData Fingerprint where rnf (Fingerprint _ _) = () -#endif ---------------------------------------------------------------------------- -- Foreign.Ptr @@ -730,13 +716,11 @@ instance NFData CClock where rnf = rwhnf -- |@since 1.4.0.0 instance NFData CTime where rnf = rwhnf -#if MIN_VERSION_base(4,4,0) -- |@since 1.4.0.0 instance NFData CUSeconds where rnf = rwhnf -- |@since 1.4.0.0 instance NFData CSUSeconds where rnf = rwhnf -#endif -- |@since 1.4.0.0 instance NFData CFloat where rnf = rwhnf diff --git a/changelog.md b/changelog.md index 8f95f22..3e71473 100644 --- a/changelog.md +++ b/changelog.md @@ -15,6 +15,7 @@ * Add `NFData1` and `NFData2` type classes ([#8](https://github.com/haskell/deepseq/issues/8)) * Add `NFData1` and `NFData` instances for `Data.Functor.{Compose,Sum,Product}` ([#30](https://github.com/haskell/deepseq/pull/30)) + * Drop support for GHC 7.0 & GHC 7.2 ## 1.4.2.0 *Apr 2016* diff --git a/deepseq.cabal b/deepseq.cabal index 1883377..d5945f4 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -22,12 +22,11 @@ description: data types. build-type: Simple cabal-version: >=1.10 -tested-with: GHC==8.0.1, +tested-with: GHC==8.2.1, GHC==8.0.2, GHC==8.0.1, GHC==7.10.3, GHC==7.10.2, GHC==7.10.1, GHC==7.8.4, GHC==7.8.3, GHC==7.8.2, GHC==7.8.1, GHC==7.6.3, GHC==7.6.2, GHC==7.6.1, - GHC==7.4.2, GHC==7.4.1, GHC==7.2.2, GHC==7.2.1, - GHC==7.0.4, GHC==7.0.3, GHC==7.0.2, GHC==7.0.1 + GHC==7.4.2, GHC==7.4.1 extra-source-files: changelog.md @@ -41,30 +40,28 @@ library BangPatterns CPP - if impl(ghc>=7.2) - -- Enable Generics-backed DefaultSignatures for `rnf` - other-extensions: - DefaultSignatures - GADTs - FlexibleContexts - FlexibleInstances - MultiParamTypeClasses - Safe - TypeOperators + -- Enable Generics-backed DefaultSignatures for `rnf` + other-extensions: + DefaultSignatures + GADTs + FlexibleContexts + FlexibleInstances + MultiParamTypeClasses + Safe + TypeOperators - -- GHC.Generics lived in `ghc-prim` for GHC 7.2 & GHC 7.4 - if impl(ghc < 7.6) - build-depends: ghc-prim == 0.2.* + -- GHC.Generics lived in `ghc-prim` for GHC 7.2 & GHC 7.4 + if impl(ghc == 7.4.*) + build-depends: ghc-prim == 0.2.* - if impl(ghc>=7.8) - other-extensions: - EmptyCase + if impl(ghc>=7.6) + other-extensions: PolyKinds - if impl(ghc < 7.4) - build-depends: array < 0.4 + if impl(ghc>=7.8) + other-extensions: EmptyCase - build-depends: base >= 4.3 && < 4.11, - array >= 0.3 && < 0.6 + build-depends: base >= 4.5 && < 4.11, + array >= 0.4 && < 0.6 ghc-options: -Wall exposed-modules: Control.DeepSeq From git at git.haskell.org Wed Jul 19 21:59:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:42 +0000 (UTC) Subject: [commit: packages/deepseq] master: Add NFData instance for Foreign.C.Types.CBool (a57a114) Message-ID: <20170719215942.0EB973A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/a57a114e0b6c26f099bb3a61480d8a44ac5c3703 >--------------------------------------------------------------- commit a57a114e0b6c26f099bb3a61480d8a44ac5c3703 Author: Ryan Scott Date: Sat Apr 8 14:00:08 2017 -0400 Add NFData instance for Foreign.C.Types.CBool >--------------------------------------------------------------- a57a114e0b6c26f099bb3a61480d8a44ac5c3703 Control/DeepSeq.hs | 5 +++++ changelog.md | 1 + 2 files changed, 6 insertions(+) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 4c5505e..41227c0 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -757,6 +757,11 @@ instance NFData CFpos where rnf = rwhnf -- |@since 1.4.0.0 instance NFData CJmpBuf where rnf = rwhnf +#if MIN_VERSION_base(4,10,0) +-- | @since 1.4.3.0 +instance NFData CBool where rnf = rwhnf +#endif + ---------------------------------------------------------------------------- -- System.Exit diff --git a/changelog.md b/changelog.md index 8f95f22..c939cdb 100644 --- a/changelog.md +++ b/changelog.md @@ -15,6 +15,7 @@ * Add `NFData1` and `NFData2` type classes ([#8](https://github.com/haskell/deepseq/issues/8)) * Add `NFData1` and `NFData` instances for `Data.Functor.{Compose,Sum,Product}` ([#30](https://github.com/haskell/deepseq/pull/30)) + * Add `NFData` instance for `Foreign.C.Types.CBool` ## 1.4.2.0 *Apr 2016* From git at git.haskell.org Wed Jul 19 21:59:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:44 +0000 (UTC) Subject: [commit: packages/deepseq] master: Drop support and CPP for GHC 7.0 & GHC 7.2 (36f6a84) Message-ID: <20170719215944.14E543A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/36f6a84927afcbf26d1f34d3c7ee6da545fa07df >--------------------------------------------------------------- commit 36f6a84927afcbf26d1f34d3c7ee6da545fa07df Author: Herbert Valerio Riedel Date: Sun Apr 16 01:30:34 2017 +0200 Drop support and CPP for GHC 7.0 & GHC 7.2 ...and add GHC 8.2.1 to CI matrix >--------------------------------------------------------------- 36f6a84927afcbf26d1f34d3c7ee6da545fa07df .travis.yml | 26 ++++---------------------- Control/DeepSeq.hs | 24 ++++-------------------- changelog.md | 1 + deepseq.cabal | 44 +++++++++++++++++++++----------------------- 4 files changed, 30 insertions(+), 65 deletions(-) diff --git a/.travis.yml b/.travis.yml index bdcaaaf..31ade0e 100644 --- a/.travis.yml +++ b/.travis.yml @@ -13,24 +13,6 @@ before_cache: matrix: include: - - env: CABALVER=1.24 GHCVER=7.0.1 - compiler: ": #GHC 7.0.1" - addons: {apt: {packages: [cabal-install-1.24,ghc-7.0.1], sources: [hvr-ghc]}} - - env: CABALVER=1.24 GHCVER=7.0.2 - compiler: ": #GHC 7.0.2" - addons: {apt: {packages: [cabal-install-1.24,ghc-7.0.2], sources: [hvr-ghc]}} - - env: CABALVER=1.24 GHCVER=7.0.3 - compiler: ": #GHC 7.0.3" - addons: {apt: {packages: [cabal-install-1.24,ghc-7.0.3], sources: [hvr-ghc]}} - - env: CABALVER=1.24 GHCVER=7.0.4 - compiler: ": #GHC 7.0.4" - addons: {apt: {packages: [cabal-install-1.24,ghc-7.0.4], sources: [hvr-ghc]}} - - env: CABALVER=1.24 GHCVER=7.2.1 - compiler: ": #GHC 7.2.1" - addons: {apt: {packages: [cabal-install-1.24,ghc-7.2.1], sources: [hvr-ghc]}} - - env: CABALVER=1.24 GHCVER=7.2.2 - compiler: ": #GHC 7.2.2" - addons: {apt: {packages: [cabal-install-1.24,ghc-7.2.2], sources: [hvr-ghc]}} - env: CABALVER=1.24 GHCVER=7.4.1 compiler: ": #GHC 7.4.1" addons: {apt: {packages: [cabal-install-1.24,ghc-7.4.1], sources: [hvr-ghc]}} @@ -73,14 +55,14 @@ matrix: - env: CABALVER=1.24 GHCVER=8.0.2 compiler: ": #GHC 8.0.2" addons: {apt: {packages: [cabal-install-1.24,ghc-8.0.2], sources: [hvr-ghc]}} + - env: CABALVER=2.0 GHCVER=8.2.1 + compiler: ": #GHC 8.2.1" + addons: {apt: {packages: [cabal-install-2.0,ghc-8.2.1], sources: [hvr-ghc]}} before_install: - unset CC - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH - - if [ "$GHCVER" != "7.2.1" ]; - then - export TEST_OPTS="--enable-tests --enable-benchmarks"; - fi + - export TEST_OPTS="--enable-tests --enable-benchmarks"; install: - cabal --version diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 41227c0..52e94d4 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -1,22 +1,21 @@ {-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} -#if __GLASGOW_HASKELL__ >= 702 {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} -{-# LANGUAGE TypeOperators #-} -# if MIN_VERSION_array(0,4,0) {-# LANGUAGE Safe #-} -# endif -#endif +{-# LANGUAGE TypeOperators #-} + #if __GLASGOW_HASKELL__ >= 706 {-# LANGUAGE PolyKinds #-} #endif + #if __GLASGOW_HASKELL__ >= 708 {-# LANGUAGE EmptyCase #-} #endif + ----------------------------------------------------------------------------- -- | -- Module : Control.DeepSeq @@ -116,7 +115,6 @@ import GHC.Stack ( CallStack(..) ) import GHC.SrcLoc ( SrcLoc(..) ) #endif -#if __GLASGOW_HASKELL__ >= 702 import GHC.Fingerprint.Type ( Fingerprint(..) ) import GHC.Generics @@ -166,7 +164,6 @@ instance NFData1 f => GNFData One (Rec1 f) where instance (NFData1 f, GNFData One g) => GNFData One (f :.: g) where grnf args = liftRnf (grnf args) . unComp1 -#endif infixr 0 $!! @@ -325,11 +322,8 @@ class NFData a where -- rnf :: a -> () -#if __GLASGOW_HASKELL__ >= 702 default rnf :: (Generic a, GNFData Zero (Rep a)) => a -> () rnf = grnf RnfArgs0 . from -#endif - -- | A class of functors that can be fully evaluated. -- @@ -342,10 +336,8 @@ class NFData1 f where -- See 'rnf' for the generic deriving. liftRnf :: (a -> ()) -> f a -> () -#if __GLASGOW_HASKELL__ >= 702 default liftRnf :: (Generic1 f, GNFData One (Rep1 f)) => (a -> ()) -> f a -> () liftRnf r = grnf (RnfArgs1 r) . from1 -#endif -- |@since 1.4.3.0 rnf1 :: (NFData1 f, NFData a) => f a -> () @@ -460,11 +452,7 @@ instance (Integral a, NFData a) => NFData (Ratio a) where #endif rnf x = rnf (numerator x, denominator x) -#if MIN_VERSION_base(4,4,0) instance (NFData a) => NFData (Complex a) where -#else -instance (RealFloat a, NFData a) => NFData (Complex a) where -#endif rnf (x:+y) = rnf x `seq` rnf y `seq` () @@ -641,11 +629,9 @@ instance NFData1 MVar where ---------------------------------------------------------------------------- -- GHC Specifics -#if __GLASGOW_HASKELL__ >= 702 -- |@since 1.4.0.0 instance NFData Fingerprint where rnf (Fingerprint _ _) = () -#endif ---------------------------------------------------------------------------- -- Foreign.Ptr @@ -730,13 +716,11 @@ instance NFData CClock where rnf = rwhnf -- |@since 1.4.0.0 instance NFData CTime where rnf = rwhnf -#if MIN_VERSION_base(4,4,0) -- |@since 1.4.0.0 instance NFData CUSeconds where rnf = rwhnf -- |@since 1.4.0.0 instance NFData CSUSeconds where rnf = rwhnf -#endif -- |@since 1.4.0.0 instance NFData CFloat where rnf = rwhnf diff --git a/changelog.md b/changelog.md index c939cdb..e75d8ad 100644 --- a/changelog.md +++ b/changelog.md @@ -16,6 +16,7 @@ * Add `NFData1` and `NFData` instances for `Data.Functor.{Compose,Sum,Product}` ([#30](https://github.com/haskell/deepseq/pull/30)) * Add `NFData` instance for `Foreign.C.Types.CBool` + * Drop support for GHC 7.0 & GHC 7.2 ## 1.4.2.0 *Apr 2016* diff --git a/deepseq.cabal b/deepseq.cabal index 1883377..e5de8e0 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -22,12 +22,12 @@ description: data types. build-type: Simple cabal-version: >=1.10 -tested-with: GHC==8.0.1, +tested-with: GHC==8.2.1, + GHC==8.0.2, GHC==8.0.1, GHC==7.10.3, GHC==7.10.2, GHC==7.10.1, GHC==7.8.4, GHC==7.8.3, GHC==7.8.2, GHC==7.8.1, GHC==7.6.3, GHC==7.6.2, GHC==7.6.1, - GHC==7.4.2, GHC==7.4.1, GHC==7.2.2, GHC==7.2.1, - GHC==7.0.4, GHC==7.0.3, GHC==7.0.2, GHC==7.0.1 + GHC==7.4.2, GHC==7.4.1 extra-source-files: changelog.md @@ -41,30 +41,28 @@ library BangPatterns CPP - if impl(ghc>=7.2) - -- Enable Generics-backed DefaultSignatures for `rnf` - other-extensions: - DefaultSignatures - GADTs - FlexibleContexts - FlexibleInstances - MultiParamTypeClasses - Safe - TypeOperators + -- Enable Generics-backed DefaultSignatures for `rnf` + other-extensions: + DefaultSignatures + GADTs + FlexibleContexts + FlexibleInstances + MultiParamTypeClasses + Safe + TypeOperators - -- GHC.Generics lived in `ghc-prim` for GHC 7.2 & GHC 7.4 - if impl(ghc < 7.6) - build-depends: ghc-prim == 0.2.* + -- GHC.Generics lived in `ghc-prim` for GHC 7.2 & GHC 7.4 + if impl(ghc == 7.4.*) + build-depends: ghc-prim == 0.2.* - if impl(ghc>=7.8) - other-extensions: - EmptyCase + if impl(ghc>=7.6) + other-extensions: PolyKinds - if impl(ghc < 7.4) - build-depends: array < 0.4 + if impl(ghc>=7.8) + other-extensions: EmptyCase - build-depends: base >= 4.3 && < 4.11, - array >= 0.3 && < 0.6 + build-depends: base >= 4.5 && < 4.11, + array >= 0.4 && < 0.6 ghc-options: -Wall exposed-modules: Control.DeepSeq From git at git.haskell.org Wed Jul 19 21:59:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:46 +0000 (UTC) Subject: [commit: packages/deepseq] master: Merge PR #28 (ded7a22) Message-ID: <20170719215946.1B1E33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/ded7a2282271ceae8988f7f46753b69d593df84e >--------------------------------------------------------------- commit ded7a2282271ceae8988f7f46753b69d593df84e Merge: 36f6a84 0792252 Author: Herbert Valerio Riedel Date: Sun Apr 16 09:10:27 2017 +0200 Merge PR #28 >--------------------------------------------------------------- ded7a2282271ceae8988f7f46753b69d593df84e Control/DeepSeq.hs | 4 ++-- changelog.md | 1 + 2 files changed, 3 insertions(+), 2 deletions(-) diff --cc changelog.md index e75d8ad,dc66b87..83f9997 --- a/changelog.md +++ b/changelog.md @@@ -13,10 -13,7 +13,11 @@@ ([#13](https://github.com/haskell/deepseq/issues/13)) * Add `NFData Ordering` ([#25](https://github.com/haskell/deepseq/pull/25)) * Add `NFData1` and `NFData2` type classes ([#8](https://github.com/haskell/deepseq/issues/8)) + * Add `NFData1` and `NFData` instances for `Data.Functor.{Compose,Sum,Product}` + ([#30](https://github.com/haskell/deepseq/pull/30)) + * Add `NFData` instance for `Foreign.C.Types.CBool` + * Drop support for GHC 7.0 & GHC 7.2 + * Expose `NFData` instance for `Down` on earlier versions of `base` ## 1.4.2.0 *Apr 2016* From git at git.haskell.org Wed Jul 19 21:59:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:48 +0000 (UTC) Subject: [commit: packages/deepseq] master: Add SafeHaskell Backdoor (02909d3) Message-ID: <20170719215948.211433A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/02909d39c0465c1ea6ee8bbf45f8862afe91134b >--------------------------------------------------------------- commit 02909d39c0465c1ea6ee8bbf45f8862afe91134b Author: Herbert Valerio Riedel Date: Sun Apr 16 09:25:46 2017 +0200 Add SafeHaskell Backdoor This was made necessary by #28 This hack reduces the surface-area requiring TRUSTWORTHY annotations >--------------------------------------------------------------- 02909d39c0465c1ea6ee8bbf45f8862afe91134b Control/DeepSeq.hs | 2 +- Control/DeepSeq/BackDoor.hs | 18 ++++++++++++++++++ deepseq.cabal | 4 +--- 3 files changed, 20 insertions(+), 4 deletions(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 233f538..f4c8488 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -88,7 +88,7 @@ import System.Mem.StableName ( StableName ) #if MIN_VERSION_base(4,6,0) import Data.Ord ( Down(Down) ) #else -import GHC.Exts ( Down(Down) ) +import Control.DeepSeq.BackDoor ( Down(Down) ) #endif #if MIN_VERSION_base(4,7,0) diff --git a/Control/DeepSeq/BackDoor.hs b/Control/DeepSeq/BackDoor.hs new file mode 100644 index 0000000..147a848 --- /dev/null +++ b/Control/DeepSeq/BackDoor.hs @@ -0,0 +1,18 @@ +{-# LANGUAGE CPP #-} + +#if MIN_VERSION_base(4,6,0) +{-# LANGUAGE Safe #-} +#else +{-# LANGUAGE Trustworthy #-} +#endif + +-- | Hack to keep Control.DeepSeq SAFE-inferred +module Control.DeepSeq.BackDoor + ( module X + ) where + +#if MIN_VERSION_base(4,6,0) +import Data.Ord as X ( Down(Down) ) +#else +import GHC.Exts as X ( Down(Down) ) +#endif diff --git a/deepseq.cabal b/deepseq.cabal index e5de8e0..7f54e2a 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -66,12 +66,10 @@ library ghc-options: -Wall exposed-modules: Control.DeepSeq - + other-modules: Control.DeepSeq.BackDoor test-suite deepseq-generics-tests default-language: Haskell2010 - if !impl(ghc>=7.2) - buildable: False type: exitcode-stdio-1.0 hs-source-dirs: . tests main-is: Main.hs From git at git.haskell.org Wed Jul 19 21:59:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:50 +0000 (UTC) Subject: [commit: packages/deepseq] master: Merge PR #32 (e7fdd00) Message-ID: <20170719215950.279243A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/e7fdd00099854aa0a35cdcf55b044dc450352e69 >--------------------------------------------------------------- commit e7fdd00099854aa0a35cdcf55b044dc450352e69 Merge: 02909d3 af54b3e Author: Herbert Valerio Riedel Date: Sun Apr 16 09:40:13 2017 +0200 Merge PR #32 ...this required to update C.D.BackDoor >--------------------------------------------------------------- e7fdd00099854aa0a35cdcf55b044dc450352e69 Control/DeepSeq.hs | 22 ++++++++++++++++++++++ Control/DeepSeq/BackDoor.hs | 9 ++++++++- changelog.md | 2 ++ 3 files changed, 32 insertions(+), 1 deletion(-) diff --cc Control/DeepSeq.hs index f4c8488,26167af..97e040a --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@@ -93,8 -92,9 +93,14 @@@ import Control.DeepSeq.BackDoor ( Down( #if MIN_VERSION_base(4,7,0) import Data.Proxy ( Proxy(Proxy) ) -import Data.Type.Equality +#endif + ++#if MIN_VERSION_base(4,10,0) ++import Data.Type.Equality ( (:~:), (:~~:) ) ++#elif MIN_VERSION_base(4,7,0) ++import Control.DeepSeq.BackDoor ( (:~:) ) + #endif + #if MIN_VERSION_base(4,8,0) import Data.Functor.Identity ( Identity(..) ) import Data.Typeable ( TypeRep, TyCon, rnfTypeRep, rnfTyCon ) diff --cc Control/DeepSeq/BackDoor.hs index 147a848,0000000..c231245 mode 100644,000000..100644 --- a/Control/DeepSeq/BackDoor.hs +++ b/Control/DeepSeq/BackDoor.hs @@@ -1,18 -1,0 +1,25 @@@ +{-# LANGUAGE CPP #-} + - #if MIN_VERSION_base(4,6,0) ++#if MIN_VERSION_base(4,10,0) +{-# LANGUAGE Safe #-} +#else +{-# LANGUAGE Trustworthy #-} +#endif + +-- | Hack to keep Control.DeepSeq SAFE-inferred +module Control.DeepSeq.BackDoor + ( module X + ) where + +#if MIN_VERSION_base(4,6,0) ++-- SAFE +import Data.Ord as X ( Down(Down) ) +#else ++-- not SAFE +import GHC.Exts as X ( Down(Down) ) +#endif ++ ++#if MIN_VERSION_base(4,7,0) ++-- Data.Type.Equality wasn't SAFE before base-4.10 ++import Data.Type.Equality as X ( (:~:) ) ++#endif diff --cc changelog.md index 83f9997,fef1ead..4da3e7c --- a/changelog.md +++ b/changelog.md @@@ -15,9 -15,8 +15,11 @@@ * Add `NFData1` and `NFData2` type classes ([#8](https://github.com/haskell/deepseq/issues/8)) * Add `NFData1` and `NFData` instances for `Data.Functor.{Compose,Sum,Product}` ([#30](https://github.com/haskell/deepseq/pull/30)) + * Add `NFData`, `NFData1`, and `NFData2` instances for `(:~:)` and `(:~~:)` + from `Data.Type.Equality` ([#31](https://github.com/haskell/deepseq/issues/31)) + * Add `NFData` instance for `Foreign.C.Types.CBool` + * Drop support for GHC 7.0 & GHC 7.2 + * Expose `NFData` instance for `Down` on earlier versions of `base` ## 1.4.2.0 *Apr 2016* From git at git.haskell.org Wed Jul 19 21:59:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:52 +0000 (UTC) Subject: [commit: packages/deepseq] master: Harden Control.DeepSeq.BackDoor (067cd08) Message-ID: <20170719215952.2D4E83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/067cd08cd2e435943da7656d9e3562ce0cb71519 >--------------------------------------------------------------- commit 067cd08cd2e435943da7656d9e3562ce0cb71519 Author: Herbert Valerio Riedel Date: Sun Apr 16 10:03:36 2017 +0200 Harden Control.DeepSeq.BackDoor This makes sure that the compiler has a better chance to warn/complain if we forget to update the BackDoor module when `base` changes >--------------------------------------------------------------- 067cd08cd2e435943da7656d9e3562ce0cb71519 Control/DeepSeq.hs | 2 ++ Control/DeepSeq/BackDoor.hs | 23 +++++++++++++++-------- 2 files changed, 17 insertions(+), 8 deletions(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 97e040a..0a0439f 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -97,6 +97,8 @@ import Data.Proxy ( Proxy(Proxy) ) #if MIN_VERSION_base(4,10,0) import Data.Type.Equality ( (:~:), (:~~:) ) +#elif MIN_VERSION_base(4,9,0) +import Data.Type.Equality ( (:~:) ) #elif MIN_VERSION_base(4,7,0) import Control.DeepSeq.BackDoor ( (:~:) ) #endif diff --git a/Control/DeepSeq/BackDoor.hs b/Control/DeepSeq/BackDoor.hs index c231245..356254b 100644 --- a/Control/DeepSeq/BackDoor.hs +++ b/Control/DeepSeq/BackDoor.hs @@ -1,25 +1,32 @@ {-# LANGUAGE CPP #-} -#if MIN_VERSION_base(4,10,0) +#if MIN_VERSION_base(4,9,0) || (MIN_VERSION_base(4,6,0) && !MIN_VERSION_base(4,7,0)) {-# LANGUAGE Safe #-} + +module Control.DeepSeq.BackDoor + {-# WARNING "This module is empty! Do not import me!" #-} + () where + #else {-# LANGUAGE Trustworthy #-} -#endif -- | Hack to keep Control.DeepSeq SAFE-inferred +-- +-- This module only re-export reasonably safe entities from non-safe +-- modules when there is no safe alternative module Control.DeepSeq.BackDoor ( module X ) where -#if MIN_VERSION_base(4,6,0) --- SAFE -import Data.Ord as X ( Down(Down) ) -#else +#if !(MIN_VERSION_base(4,6,0)) -- not SAFE import GHC.Exts as X ( Down(Down) ) #endif -#if MIN_VERSION_base(4,7,0) --- Data.Type.Equality wasn't SAFE before base-4.10 +#if MIN_VERSION_base(4,10,0) +-- Data.Type.Equality SAFE starting with base-4.10 +#elif MIN_VERSION_base(4,7,0) import Data.Type.Equality as X ( (:~:) ) #endif + +#endif From git at git.haskell.org Wed Jul 19 21:59:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:54 +0000 (UTC) Subject: [commit: packages/deepseq] master: Reformat and augment changelog entry for 1.4.3 (bb36922) Message-ID: <20170719215954.329233A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/bb36922b594dd2a06ad5f4cf21a4365ce626dbfd >--------------------------------------------------------------- commit bb36922b594dd2a06ad5f4cf21a4365ce626dbfd Author: Herbert Valerio Riedel Date: Sun Apr 16 10:37:17 2017 +0200 Reformat and augment changelog entry for 1.4.3 [skip ci] >--------------------------------------------------------------- bb36922b594dd2a06ad5f4cf21a4365ce626dbfd changelog.md | 34 ++++++++++++++++++++++++++-------- 1 file changed, 26 insertions(+), 8 deletions(-) diff --git a/changelog.md b/changelog.md index 4da3e7c..89eacc4 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,10 @@ # Changelog for [`deepseq` package](http://hackage.haskell.org/package/deepseq) -## 1.4.3.0 *TBD* +## 1.4.3.0 *Apr 2017* + + * Bundled with GHC 8.2.1 + + * Drop support for GHC 7.0 & GHC 7.2 * Changed behavior of generic `NFData` instances for constructor-less data types. Before, a generic `rnf` implementation would always `error` on a @@ -8,18 +12,32 @@ the argument is a diverging computation, a generic `rnf` implementation will actually trigger the diverging computation. ([#19](https://github.com/haskell/deepseq/issues/19)) - * Add `rwhnf !_ = ()` ([#3](https://github.com/haskell/deepseq/issues/3)) + + * Add new `rwhnf` function defined as `rwhnf !_ = ()` + ([#3](https://github.com/haskell/deepseq/issues/3)) + * Add `(<$!!>) :: (Monad m, NFData b) => (a -> b) -> m a -> m b` ([#13](https://github.com/haskell/deepseq/issues/13)) - * Add `NFData Ordering` ([#25](https://github.com/haskell/deepseq/pull/25)) - * Add `NFData1` and `NFData2` type classes ([#8](https://github.com/haskell/deepseq/issues/8)) + + * Add `NFData1` and `NFData2` type classes + ([#8](https://github.com/haskell/deepseq/issues/8)) + + * Add `NFData` instance for `Down` for `base` versions prior to + `base-4.6.0` which didn't yet export it it via `Data.Ord` + ([#28](https://github.com/haskell/deepseq/pull/28)) + + * Add `NFData` instance for `Foreign.C.Types.CBool` + ([#33](https://github.com/haskell/deepseq/pull/33)) + + * Add `NFData` instance for `Ordering` + ([#25](https://github.com/haskell/deepseq/pull/25)) + * Add `NFData1` and `NFData` instances for `Data.Functor.{Compose,Sum,Product}` ([#30](https://github.com/haskell/deepseq/pull/30)) + * Add `NFData`, `NFData1`, and `NFData2` instances for `(:~:)` and `(:~~:)` - from `Data.Type.Equality` ([#31](https://github.com/haskell/deepseq/issues/31)) - * Add `NFData` instance for `Foreign.C.Types.CBool` - * Drop support for GHC 7.0 & GHC 7.2 - * Expose `NFData` instance for `Down` on earlier versions of `base` + from `Data.Type.Equality` + ([#31](https://github.com/haskell/deepseq/issues/31)) ## 1.4.2.0 *Apr 2016* From git at git.haskell.org Wed Jul 19 21:59:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:56 +0000 (UTC) Subject: [commit: packages/deepseq] master: Follow-up to bb36922b594d [skip ci] (65dd864) Message-ID: <20170719215956.384E73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/65dd864d0d2f5cf415064fc214261b9270a924cf >--------------------------------------------------------------- commit 65dd864d0d2f5cf415064fc214261b9270a924cf Author: Herbert Valerio Riedel Date: Sun Apr 16 10:41:40 2017 +0200 Follow-up to bb36922b594d [skip ci] >--------------------------------------------------------------- 65dd864d0d2f5cf415064fc214261b9270a924cf changelog.md | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/changelog.md b/changelog.md index 89eacc4..4f53310 100644 --- a/changelog.md +++ b/changelog.md @@ -6,11 +6,12 @@ * Drop support for GHC 7.0 & GHC 7.2 - * Changed behavior of generic `NFData` instances for constructor-less data - types. Before, a generic `rnf` implementation would always `error` on a - data type with no constructors. Now, it will force the argument, so if - the argument is a diverging computation, a generic `rnf` implementation - will actually trigger the diverging computation. + * Changed strictness behavior of generic `NFData` instances for + constructor-less data types. Before, a generic `rnf` + implementation would always `error` on a data type with no + constructors. Now, it will force the argument, so if the argument + is a diverging computation, a generic `rnf` implementation will + actually trigger the diverging computation. ([#19](https://github.com/haskell/deepseq/issues/19)) * Add new `rwhnf` function defined as `rwhnf !_ = ()` @@ -23,7 +24,7 @@ ([#8](https://github.com/haskell/deepseq/issues/8)) * Add `NFData` instance for `Down` for `base` versions prior to - `base-4.6.0` which didn't yet export it it via `Data.Ord` + `base-4.6.0` which didn't yet export it via `Data.Ord` ([#28](https://github.com/haskell/deepseq/pull/28)) * Add `NFData` instance for `Foreign.C.Types.CBool` From git at git.haskell.org Wed Jul 19 21:59:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 21:59:58 +0000 (UTC) Subject: [commit: packages/deepseq] master: Minor optimisation for `<$!!>` (3b78f38) Message-ID: <20170719215958.3D8693A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/3b78f384818986a7d249002f83a47f1f637e2d41 >--------------------------------------------------------------- commit 3b78f384818986a7d249002f83a47f1f637e2d41 Author: Herbert Valerio Riedel Date: Sun Apr 16 23:10:19 2017 +0200 Minor optimisation for `<$!!>` >--------------------------------------------------------------- 3b78f384818986a7d249002f83a47f1f637e2d41 Control/DeepSeq.hs | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 0a0439f..32d8b7d 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -244,7 +244,14 @@ force x = x `deepseq` x -- -- @since 1.4.3.0 (<$!!>) :: (Monad m, NFData b) => (a -> b) -> m a -> m b +#if MIN_VERSION_base(4,8,0) +-- Minor optimisation for AMP; this avoids the redundant indirection +-- through 'return' in case GHC isn't smart enough to optimise it away +-- on its own +f <$!!> m = m >>= \x -> pure $!! f x +#else f <$!!> m = m >>= \x -> return $!! f x +#endif infixl 4 <$!!> -- | Reduce to weak head normal form From git at git.haskell.org Wed Jul 19 22:00:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:00:00 +0000 (UTC) Subject: [commit: packages/deepseq] master: Refactor and extend documentation (0b22c98) Message-ID: <20170719220000.42DEA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/0b22c9825ef79c1ee41d2f19e7c997f5cdc93494 >--------------------------------------------------------------- commit 0b22c9825ef79c1ee41d2f19e7c997f5cdc93494 Author: Herbert Valerio Riedel Date: Sat Apr 22 10:52:39 2017 +0200 Refactor and extend documentation With the recent new API additions it makes sense to restructure a bit. Moreoever, this commit augments the new NFData1/NFData2 API with a few more haddock strings, and extends the introductory examples. >--------------------------------------------------------------- 0b22c9825ef79c1ee41d2f19e7c997f5cdc93494 Control/DeepSeq.hs | 58 ++++++++++++++++++++++++++++++++++++--------- Control/DeepSeq/BackDoor.hs | 9 +++---- 2 files changed, 52 insertions(+), 15 deletions(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 32d8b7d..7296b97 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -26,21 +26,29 @@ -- Stability : stable -- Portability : portable -- --- This module provides an overloaded function, 'deepseq', for fully --- evaluating data structures (that is, evaluating to \"Normal Form\"). +-- This module provides overloaded functions, such as 'deepseq' and +-- 'rnf', for fully evaluating data structures (that is, evaluating to +-- \"Normal Form\"). -- -- A typical use is to prevent resource leaks in lazy IO programs, by -- forcing all characters from a file to be read. For example: -- -- > import System.IO -- > import Control.DeepSeq +-- > import Control.Exception (evaluate) -- > --- > main = do --- > h <- openFile "f" ReadMode +-- > readFile' :: FilePath -> IO String +-- > readFile' fn = do +-- > h <- openFile fn ReadMode -- > s <- hGetContents h --- > s `deepseq` hClose h +-- > evaluate (rnf s) +-- > hClose h -- > return s -- +-- __Note__: The example above should rather be written in terms of +-- 'Control.Exception.bracket' to ensure releasing file-descriptors in +-- a timely matter (see the description of 'force' for an example). +-- -- 'deepseq' differs from 'seq' as it traverses data structures deeply, -- for example, 'seq' will evaluate only to the first constructor in -- the list: @@ -61,10 +69,20 @@ -- -- @since 1.1.0.0 module Control.DeepSeq ( - deepseq, ($!!), force, (<$!!>), rwhnf, - NFData(..), - NFData1(..), rnf1, - NFData2(..), rnf2 + -- * 'NFData' class + NFData(rnf), + -- * Helper functions + deepseq, + force, + ($!!), + (<$!!>), + rwhnf, + + -- * Liftings of the 'NFData' class + -- ** For unary constructors + NFData1(liftRnf), rnf1, + -- ** For binary constructors + NFData2(liftRnf2), rnf2, ) where import Control.Applicative @@ -236,6 +254,12 @@ f $!! x = x `deepseq` f x -- > {- 'result' will be fully evaluated at this point -} -- > return () -- +-- Finally, here's an exception safe variant of the @readFile'@ example: +-- +-- > readFile' :: FilePath -> IO String +-- > readFile' fn = bracket (openFile fn ReadMode) hClose $ \h -> +-- > evaluate . force =<< hGetContents h +-- -- @since 1.2.0.0 force :: (NFData a) => a -> a force x = x `deepseq` x @@ -256,6 +280,8 @@ infixl 4 <$!!> -- | Reduce to weak head normal form -- +-- Equivalent to @\\x -> 'seq' x ()@. +-- -- Useful for defining 'NFData' for types for which NF=WHNF holds. -- -- > data T = C1 | C2 | C3 @@ -356,7 +382,9 @@ class NFData1 f where default liftRnf :: (Generic1 f, GNFData One (Rep1 f)) => (a -> ()) -> f a -> () liftRnf r = grnf (RnfArgs1 r) . from1 --- |@since 1.4.3.0 +-- | Lift the standard 'rnf' function through the type constructor. +-- +-- @since 1.4.3.0 rnf1 :: (NFData1 f, NFData a) => f a -> () rnf1 = liftRnf rnf @@ -364,9 +392,17 @@ rnf1 = liftRnf rnf -- -- @since 1.4.3.0 class NFData2 p where + -- | 'liftRnf2' should reduce its argument to normal form (that + -- is, fully evaluate all sub-components), given functions to + -- reduce @a@ and @b@ arguments respectively, and then return '()'. + -- + -- __Note__: Unlike for the unary 'liftRnf', there is currently no + -- support for generically deriving 'liftRnf2'. liftRnf2 :: (a -> ()) -> (b -> ()) -> p a b -> () --- |@since 1.4.3.0 +-- | Lift the standard 'rnf' function through the type constructor. +-- +-- @since 1.4.3.0 rnf2 :: (NFData2 p, NFData a, NFData b) => p a b -> () rnf2 = liftRnf2 rnf rnf diff --git a/Control/DeepSeq/BackDoor.hs b/Control/DeepSeq/BackDoor.hs index 356254b..343ec56 100644 --- a/Control/DeepSeq/BackDoor.hs +++ b/Control/DeepSeq/BackDoor.hs @@ -1,5 +1,10 @@ {-# LANGUAGE CPP #-} +-- | Hack to keep Control.DeepSeq SAFE-inferred +-- +-- This module only re-export reasonably safe entities from non-safe +-- modules when there is no safe alternative + #if MIN_VERSION_base(4,9,0) || (MIN_VERSION_base(4,6,0) && !MIN_VERSION_base(4,7,0)) {-# LANGUAGE Safe #-} @@ -10,10 +15,6 @@ module Control.DeepSeq.BackDoor #else {-# LANGUAGE Trustworthy #-} --- | Hack to keep Control.DeepSeq SAFE-inferred --- --- This module only re-export reasonably safe entities from non-safe --- modules when there is no safe alternative module Control.DeepSeq.BackDoor ( module X ) where From git at git.haskell.org Wed Jul 19 22:04:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:00 +0000 (UTC) Subject: [commit: packages/unix] branch 'backpack' created Message-ID: <20170719220400.85A5D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix New branch : backpack Referencing: 72529f3d5920024c239119b2f028019784b20ce4 From git at git.haskell.org Wed Jul 19 22:04:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:02 +0000 (UTC) Subject: [commit: packages/unix] branch 'readdirstream-maybe-patch' created Message-ID: <20170719220402.863113A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix New branch : readdirstream-maybe-patch Referencing: 7c89170c19db81b76fbcda8c73e6c6fd9f364f00 From git at git.haskell.org Wed Jul 19 22:04:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:06 +0000 (UTC) Subject: [commit: packages/unix] tag 'v2.7.2.2' created Message-ID: <20170719220406.87D293A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix New tag : v2.7.2.2 Referencing: 3c96934184ca8902c50be6035eb9af699b9af23b From git at git.haskell.org Wed Jul 19 22:04:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:04 +0000 (UTC) Subject: [commit: packages/unix] branch 'bgamari-patch-1' created Message-ID: <20170719220404.86FA23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix New branch : bgamari-patch-1 Referencing: adefe0c3d715fe61bd57bede87ed8783c0af7f18 From git at git.haskell.org Wed Jul 19 22:04:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:08 +0000 (UTC) Subject: [commit: packages/unix] backpack, bgamari-patch-1, master, readdirstream-maybe-patch: Add GHC 7.10.2/3 and 8.0.1 to travis.yml (7207bae) Message-ID: <20170719220408.8E92A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: backpack,bgamari-patch-1,master,readdirstream-maybe-patch Link : http://ghc.haskell.org/trac/ghc/changeset/7207bae8e0a5a0885041728f11f19fde46ed0066/unix >--------------------------------------------------------------- commit 7207bae8e0a5a0885041728f11f19fde46ed0066 Author: Eric Mertens Date: Thu Jun 2 08:15:28 2016 -0700 Add GHC 7.10.2/3 and 8.0.1 to travis.yml >--------------------------------------------------------------- 7207bae8e0a5a0885041728f11f19fde46ed0066 .travis.yml | 3 +++ 1 file changed, 3 insertions(+) diff --git a/.travis.yml b/.travis.yml index 19ac588..e676991 100644 --- a/.travis.yml +++ b/.travis.yml @@ -9,6 +9,9 @@ env: - CABALVER=1.18 GHCVER=7.8.3 - CABALVER=1.18 GHCVER=7.8.4 - CABALVER=1.22 GHCVER=7.10.1 + - CABALVER=1.22 GHCVER=7.10.2 + - CABALVER=1.22 GHCVER=7.10.3 + - CABALVER=1.24 GHCVER=8.0.1 - CABALVER=head GHCVER=head matrix: From git at git.haskell.org Wed Jul 19 22:04:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:10 +0000 (UTC) Subject: [commit: packages/unix] backpack, bgamari-patch-1, master, readdirstream-maybe-patch: Testsuite: remove no_stdin (40820da) Message-ID: <20170719220410.94A8E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: backpack,bgamari-patch-1,master,readdirstream-maybe-patch Link : http://ghc.haskell.org/trac/ghc/changeset/40820da5fb35c53aed53c211277c3e6077c1ddf9/unix >--------------------------------------------------------------- commit 40820da5fb35c53aed53c211277c3e6077c1ddf9 Author: Thomas Miedema Date: Fri Jun 24 17:19:37 2016 +0200 Testsuite: remove no_stdin `no_stdin` is no longer necessary, and has been removed from the testsuite driver >--------------------------------------------------------------- 40820da5fb35c53aed53c211277c3e6077c1ddf9 tests/all.T | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/tests/all.T b/tests/all.T index d878292..e2fcb88 100644 --- a/tests/all.T +++ b/tests/all.T @@ -11,19 +11,19 @@ test('forkprocess01', extra_ways(['threaded1_ls']), compile_and_run, # user001 may fail due to this bug in glibc: # http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=466647 # -# user001 may also fail on GNU/Linux when using a terminal emulator that doesn't -# write login records to /var/run/utmp. Running: -# $ logname -# should print your login name. If it doesn't, the getLoginName test in user001 -# will fail, and that's why you are here. Try xterm. -# # Ticket #1487. The glibc implementation of getlogin, which is called by # getLoginName, requires that a terminal is connected to filedescriptor 0. # See: https://sourceware.org/git/?p=glibc.git;a=blob;f=sysdeps/unix/getlogin.c -# Therefore, we use the no_stdin option, and have to omit the 'ghci' way, -# because it relies on redirecting stdin from file. +# Therefore we have to omit the 'ghci' way, because it relies on redirecting +# stdin from file. +# +# But getLoginName also fails on GNU/Linux when using a terminal emulator +# that doesn't write login records to /var/run/utmp. Running: +# $ logname +# should print your login name. If it doesn't, the getLoginName test in user001 +# would fail, so we disabled that test. # -test('user001', [no_stdin, omit_ways(['ghci'])], compile_and_run, ['-package unix']) +test('user001', omit_ways(['ghci']), compile_and_run, ['-package unix']) test('resourceLimit', normal, compile_and_run, ['-package unix']) x86FreeBsdFail = when(platform('i386-unknown-freebsd'), expect_fail) From git at git.haskell.org Wed Jul 19 22:04:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:12 +0000 (UTC) Subject: [commit: packages/unix] backpack: Backpack'ify System.Posix.Env. (72529f3) Message-ID: <20170719220412.A0DC63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : backpack Link : http://ghc.haskell.org/trac/ghc/changeset/72529f3d5920024c239119b2f028019784b20ce4/unix >--------------------------------------------------------------- commit 72529f3d5920024c239119b2f028019784b20ce4 Author: Edward Z. Yang Date: Mon Aug 8 22:44:57 2016 -0700 Backpack'ify System.Posix.Env. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 72529f3d5920024c239119b2f028019784b20ce4 impls/Str/ByteString.hs | 67 +++++++++++ impls/Str/String.hs | 92 +++++++++++++++ unix-indef/Str.hsig | 59 ++++++++++ {System => unix-indef/System}/Posix/Env.hsc | 174 +++++++++++++++++----------- unix.cabal | 53 ++++++++- 5 files changed, 374 insertions(+), 71 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 72529f3d5920024c239119b2f028019784b20ce4 From git at git.haskell.org Wed Jul 19 22:04:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:14 +0000 (UTC) Subject: [commit: packages/unix] bgamari-patch-1, master, readdirstream-maybe-patch: Fix travis build (e66273e) Message-ID: <20170719220414.A73E03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: bgamari-patch-1,master,readdirstream-maybe-patch Link : http://ghc.haskell.org/trac/ghc/changeset/e66273e9cf9a56504ab4ef007173750793e233ea/unix >--------------------------------------------------------------- commit e66273e9cf9a56504ab4ef007173750793e233ea Author: Erik de Castro Lopo Date: Tue Sep 6 19:54:36 2016 +1000 Fix travis build >--------------------------------------------------------------- e66273e9cf9a56504ab4ef007173750793e233ea .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index e676991..5a37f5b 100644 --- a/.travis.yml +++ b/.travis.yml @@ -31,7 +31,7 @@ install: script: - autoreconf -i - - cabal configure -v2 + - cabal configure - cabal build - cabal check || [ "$CABALVER" == "1.16" ] - cabal sdist From git at git.haskell.org Wed Jul 19 22:04:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:16 +0000 (UTC) Subject: [commit: packages/unix] bgamari-patch-1, master, readdirstream-maybe-patch: Merge pull request #71 from erikd/topic/travis (cd6eae1) Message-ID: <20170719220416.AD6723A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: bgamari-patch-1,master,readdirstream-maybe-patch Link : http://ghc.haskell.org/trac/ghc/changeset/cd6eae1dc5706efafcb73e9f16ac22cd0cc9fe1d/unix >--------------------------------------------------------------- commit cd6eae1dc5706efafcb73e9f16ac22cd0cc9fe1d Merge: 40820da e66273e Author: Erik de Castro Lopo Date: Tue Sep 6 21:10:55 2016 +1000 Merge pull request #71 from erikd/topic/travis Fix travis build >--------------------------------------------------------------- cd6eae1dc5706efafcb73e9f16ac22cd0cc9fe1d .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Wed Jul 19 22:04:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:18 +0000 (UTC) Subject: [commit: packages/unix] bgamari-patch-1, master, readdirstream-maybe-patch: Don't use readdir_r if deprecated (2951cd0) Message-ID: <20170719220418.B3CD63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: bgamari-patch-1,master,readdirstream-maybe-patch Link : http://ghc.haskell.org/trac/ghc/changeset/2951cd01a725c52afc6bf6a83c068cfb40504fdf/unix >--------------------------------------------------------------- commit 2951cd01a725c52afc6bf6a83c068cfb40504fdf Author: Erik de Castro Lopo Date: Tue Sep 6 19:34:40 2016 +1000 Don't use readdir_r if deprecated GNU glibc 2.23 and later deprecate `readdir_r` in favour of plain old `readdir` which in some upcoming POSIX standard is going to required to be re-entrant. Eventually we want to drop `readder_r` all together, but want to be compatible with older unixen which may not have a re-entrant `readdir`. Solution is to make systems with *known* re-entrant `readir` use that and use `readdir_r` whereever we have it and don't *know* that `readdir` is re-entrant. Closes: https://github.com/haskell/unix/issues/70 >--------------------------------------------------------------- 2951cd01a725c52afc6bf6a83c068cfb40504fdf cbits/HsUnix.c | 19 ++++++++++++++++++- changelog.md | 4 ++++ 2 files changed, 22 insertions(+), 1 deletion(-) diff --git a/cbits/HsUnix.c b/cbits/HsUnix.c index bdd1e80..08cccd5 100644 --- a/cbits/HsUnix.c +++ b/cbits/HsUnix.c @@ -37,12 +37,29 @@ int __hsunix_push_module(int fd, const char *module) } /* + * GNU glibc 2.23 and later deprecate `readdir_r` in favour of plain old + * `readdir` which in some upcoming POSIX standard is going to required to be + * re-entrant. + * Eventually we want to drop `readder_r` all together, but want to be + * compatible with older unixen which may not have a re-entrant `readdir`. + * Solution is to make systems with *known* re-entrant `readir` use that and use + * `readdir_r` whereever we have it and don't *know* that `readdir` is + * re-entrant. + */ + +#if defined (__GLIBC__) && (__GLIBC__ >= 2) && (__GLIBC_MINOR__ >= 23) +#define USE_READDIR_R 0 +#else +#define USE_READDIR_R 1 +#endif + +/* * read an entry from the directory stream; opt for the * re-entrant friendly way of doing this, if available. */ int __hscore_readdir( DIR *dirPtr, struct dirent **pDirEnt ) { -#if HAVE_READDIR_R +#if HAVE_READDIR_R && USE_READDIR_R struct dirent* p; int res; static unsigned int nm_max = (unsigned int)-1; diff --git a/changelog.md b/changelog.md index eb429cb..4bbeeb3 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,9 @@ # Changelog for [`unix` package](http://hackage.haskell.org/package/unix) +## 2.7.2.1 *Sep 2016* + + * Don't use `readdir_r` if its deprecated. + ## 2.7.2.0 *Apr 2016* * Bundled with GHC 8.0.1 From git at git.haskell.org Wed Jul 19 22:04:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:20 +0000 (UTC) Subject: [commit: packages/unix] bgamari-patch-1, master, readdirstream-maybe-patch: Merge pull request #72 from erikd/topic/readdir-deprecated (d73ba58) Message-ID: <20170719220420.B9F9F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: bgamari-patch-1,master,readdirstream-maybe-patch Link : http://ghc.haskell.org/trac/ghc/changeset/d73ba584d0c6a2befe90eedd9ff6f6bff7cccc4c/unix >--------------------------------------------------------------- commit d73ba584d0c6a2befe90eedd9ff6f6bff7cccc4c Merge: cd6eae1 2951cd0 Author: Erik de Castro Lopo Date: Wed Sep 7 08:21:25 2016 +1000 Merge pull request #72 from erikd/topic/readdir-deprecated Don't use readdir_r if deprecated >--------------------------------------------------------------- d73ba584d0c6a2befe90eedd9ff6f6bff7cccc4c cbits/HsUnix.c | 19 ++++++++++++++++++- changelog.md | 4 ++++ 2 files changed, 22 insertions(+), 1 deletion(-) From git at git.haskell.org Wed Jul 19 22:04:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:22 +0000 (UTC) Subject: [commit: packages/unix] bgamari-patch-1, master, readdirstream-maybe-patch: Fix segfault from inconsistent macro use. (748e322) Message-ID: <20170719220422.C07FC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: bgamari-patch-1,master,readdirstream-maybe-patch Link : http://ghc.haskell.org/trac/ghc/changeset/748e3224e06638639a76cbc622e9b8c17054d5df/unix >--------------------------------------------------------------- commit 748e3224e06638639a76cbc622e9b8c17054d5df Author: Edward Z. Yang Date: Wed Sep 7 17:31:02 2016 -0700 Fix segfault from inconsistent macro use. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 748e3224e06638639a76cbc622e9b8c17054d5df cbits/HsUnix.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/cbits/HsUnix.c b/cbits/HsUnix.c index 08cccd5..7c72a34 100644 --- a/cbits/HsUnix.c +++ b/cbits/HsUnix.c @@ -110,7 +110,7 @@ char *__hscore_d_name( struct dirent* d ) void __hscore_free_dirent(struct dirent *dEnt) { -#if HAVE_READDIR_R +#if HAVE_READDIR_R && USE_READDIR_R free(dEnt); #endif } From git at git.haskell.org Wed Jul 19 22:04:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:24 +0000 (UTC) Subject: [commit: packages/unix] bgamari-patch-1, master, readdirstream-maybe-patch: Merge pull request #73 from ezyang/pr/fix-segfault (7b20b4c) Message-ID: <20170719220424.C63D63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: bgamari-patch-1,master,readdirstream-maybe-patch Link : http://ghc.haskell.org/trac/ghc/changeset/7b20b4cbc35a2fea3f26c988f9b2a95640babaaa/unix >--------------------------------------------------------------- commit 7b20b4cbc35a2fea3f26c988f9b2a95640babaaa Merge: d73ba58 748e322 Author: Edward Z. Yang Date: Thu Sep 8 12:04:24 2016 -0700 Merge pull request #73 from ezyang/pr/fix-segfault Fix segfault from inconsistent macro use. >--------------------------------------------------------------- 7b20b4cbc35a2fea3f26c988f9b2a95640babaaa cbits/HsUnix.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Wed Jul 19 22:04:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:26 +0000 (UTC) Subject: [commit: packages/unix] bgamari-patch-1, master, readdirstream-maybe-patch: Add argument documentation for Env modules (fb1efd1) Message-ID: <20170719220426.CC2333A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: bgamari-patch-1,master,readdirstream-maybe-patch Link : http://ghc.haskell.org/trac/ghc/changeset/fb1efd1fd78c3125c14e69650a9eb5666527719f/unix >--------------------------------------------------------------- commit fb1efd1fd78c3125c14e69650a9eb5666527719f Author: Eric Mertens Date: Thu Oct 13 08:56:08 2016 -0700 Add argument documentation for Env modules Fixes #76 >--------------------------------------------------------------- fb1efd1fd78c3125c14e69650a9eb5666527719f System/Posix/Env.hsc | 25 ++++++++++++++++++------- System/Posix/Env/ByteString.hsc | 21 +++++++++++++++------ 2 files changed, 33 insertions(+), 13 deletions(-) diff --git a/System/Posix/Env.hsc b/System/Posix/Env.hsc index 7d5f04c..2e052ad 100644 --- a/System/Posix/Env.hsc +++ b/System/Posix/Env.hsc @@ -50,7 +50,9 @@ import qualified GHC.Foreign as GHC (newCString) -- |'getEnv' looks up a variable in the environment. -getEnv :: String -> IO (Maybe String) +getEnv :: + String {- ^ variable name -} -> + IO (Maybe String) {- ^ variable value -} getEnv name = do litstring <- withFilePath name c_getenv if litstring /= nullPtr @@ -61,7 +63,10 @@ getEnv name = do -- programmer can specify a fallback if the variable is not found -- in the environment. -getEnvDefault :: String -> String -> IO String +getEnvDefault :: + String {- ^ variable name -} -> + String {- ^ fallback value -} -> + IO String {- ^ variable value or fallback value -} getEnvDefault name fallback = liftM (fromMaybe fallback) (getEnv name) foreign import ccall unsafe "getenv" @@ -94,7 +99,7 @@ foreign import ccall unsafe "&environ" -- |'getEnvironment' retrieves the entire environment as a -- list of @(key,value)@ pairs. -getEnvironment :: IO [(String,String)] +getEnvironment :: IO [(String,String)] {- ^ @[(key,value)]@ -} getEnvironment = do env <- getEnvironmentPrim return $ map (dropEq.(break ((==) '='))) env @@ -105,7 +110,9 @@ getEnvironment = do -- |'setEnvironment' resets the entire environment to the given list of -- @(key,value)@ pairs. -setEnvironment :: [(String,String)] -> IO () +setEnvironment :: + [(String,String)] {- ^ @[(key,value)]@ -} -> + IO () setEnvironment env = do clearEnv forM_ env $ \(key,value) -> @@ -114,7 +121,7 @@ setEnvironment env = do -- |The 'unsetEnv' function deletes all instances of the variable name -- from the environment. -unsetEnv :: String -> IO () +unsetEnv :: String {- ^ variable name -} -> IO () #if HAVE_UNSETENV # if !UNSETENV_RETURNS_VOID unsetEnv name = withFilePath name $ \ s -> @@ -137,7 +144,7 @@ unsetEnv name = putEnv (name ++ "=") -- |'putEnv' function takes an argument of the form @name=value@ -- and is equivalent to @setEnv(key,value,True{-overwrite-})@. -putEnv :: String -> IO () +putEnv :: String {- ^ "key=value" -} -> IO () putEnv keyvalue = do s <- newFilePath keyvalue -- Do not free `s` after calling putenv. -- According to SUSv2, the string passed to putenv @@ -159,7 +166,11 @@ foreign import ccall unsafe "putenv" not reset, otherwise it is reset to the given value. -} -setEnv :: String -> String -> Bool {-overwrite-} -> IO () +setEnv :: + String {- ^ variable name -} -> + String {- ^ variable value -} -> + Bool {- ^ overwrite -} -> + IO () #ifdef HAVE_SETENV setEnv key value ovrwrt = do withFilePath key $ \ keyP -> diff --git a/System/Posix/Env/ByteString.hsc b/System/Posix/Env/ByteString.hsc index c6c374c..3ce867b 100644 --- a/System/Posix/Env/ByteString.hsc +++ b/System/Posix/Env/ByteString.hsc @@ -45,7 +45,9 @@ import Data.ByteString (ByteString) -- |'getEnv' looks up a variable in the environment. -getEnv :: ByteString -> IO (Maybe ByteString) +getEnv :: + ByteString {- ^ variable name -} -> + IO (Maybe ByteString) {- ^ variable value -} getEnv name = do litstring <- B.useAsCString name c_getenv if litstring /= nullPtr @@ -56,7 +58,10 @@ getEnv name = do -- programmer can specify a fallback if the variable is not found -- in the environment. -getEnvDefault :: ByteString -> ByteString -> IO ByteString +getEnvDefault :: + ByteString {- ^ variable name -} -> + ByteString {- ^ fallback value -} -> + IO ByteString {- ^ variable value or fallback value -} getEnvDefault name fallback = liftM (fromMaybe fallback) (getEnv name) foreign import ccall unsafe "getenv" @@ -86,7 +91,7 @@ foreign import ccall unsafe "&environ" -- |'getEnvironment' retrieves the entire environment as a -- list of @(key,value)@ pairs. -getEnvironment :: IO [(ByteString,ByteString)] +getEnvironment :: IO [(ByteString,ByteString)] {- ^ @[(key,value)]@ -} getEnvironment = do env <- getEnvironmentPrim return $ map (dropEq.(BC.break ((==) '='))) env @@ -98,7 +103,7 @@ getEnvironment = do -- |The 'unsetEnv' function deletes all instances of the variable name -- from the environment. -unsetEnv :: ByteString -> IO () +unsetEnv :: ByteString {- ^ variable name -} -> IO () #if HAVE_UNSETENV # if !UNSETENV_RETURNS_VOID unsetEnv name = B.useAsCString name $ \ s -> @@ -121,7 +126,7 @@ unsetEnv name = putEnv (name ++ "=") -- |'putEnv' function takes an argument of the form @name=value@ -- and is equivalent to @setEnv(key,value,True{-overwrite-})@. -putEnv :: ByteString -> IO () +putEnv :: ByteString {- ^ "key=value" -} -> IO () putEnv keyvalue = B.useAsCString keyvalue $ \s -> throwErrnoIfMinus1_ "putenv" (c_putenv s) @@ -135,7 +140,11 @@ foreign import ccall unsafe "putenv" not reset, otherwise it is reset to the given value. -} -setEnv :: ByteString -> ByteString -> Bool {-overwrite-} -> IO () +setEnv :: + ByteString {- ^ variable name -} -> + ByteString {- ^ variable value -} -> + Bool {- ^ overwrite -} -> + IO () #ifdef HAVE_SETENV setEnv key value ovrwrt = do B.useAsCString key $ \ keyP -> From git at git.haskell.org Wed Jul 19 22:04:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:28 +0000 (UTC) Subject: [commit: packages/unix] bgamari-patch-1, master: Merge pull request #77 from glguy/patch-76 (02bab3c) Message-ID: <20170719220428.D24183A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: bgamari-patch-1,master Link : http://ghc.haskell.org/trac/ghc/changeset/02bab3c5e94578052884ac44248a98c08bc4b038/unix >--------------------------------------------------------------- commit 02bab3c5e94578052884ac44248a98c08bc4b038 Merge: 7b20b4c fb1efd1 Author: Eric Mertens Date: Sat Oct 15 19:40:25 2016 -0700 Merge pull request #77 from glguy/patch-76 Add argument documentation for Env modules >--------------------------------------------------------------- 02bab3c5e94578052884ac44248a98c08bc4b038 System/Posix/Env.hsc | 25 ++++++++++++++++++------- System/Posix/Env/ByteString.hsc | 21 +++++++++++++++------ 2 files changed, 33 insertions(+), 13 deletions(-) From git at git.haskell.org Wed Jul 19 22:04:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:30 +0000 (UTC) Subject: [commit: packages/unix] bgamari-patch-1, master: Prepare for 2.7.2.1 release (113fe7a) Message-ID: <20170719220430.D824E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: bgamari-patch-1,master Link : http://ghc.haskell.org/trac/ghc/changeset/113fe7a84d47010123db9501ea2885ca86277a2d/unix >--------------------------------------------------------------- commit 113fe7a84d47010123db9501ea2885ca86277a2d Author: Herbert Valerio Riedel Date: Sat Nov 12 00:15:04 2016 +0100 Prepare for 2.7.2.1 release >--------------------------------------------------------------- 113fe7a84d47010123db9501ea2885ca86277a2d changelog.md | 4 +++- unix.cabal | 2 +- 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/changelog.md b/changelog.md index 4bbeeb3..c773d3d 100644 --- a/changelog.md +++ b/changelog.md @@ -1,9 +1,11 @@ # Changelog for [`unix` package](http://hackage.haskell.org/package/unix) -## 2.7.2.1 *Sep 2016* +## 2.7.2.1 *Nov 2016* * Don't use `readdir_r` if its deprecated. + * Add argument documentation for Env modules + ## 2.7.2.0 *Apr 2016* * Bundled with GHC 8.0.1 diff --git a/unix.cabal b/unix.cabal index 02d583e..5ba2ddd 100644 --- a/unix.cabal +++ b/unix.cabal @@ -1,5 +1,5 @@ name: unix -version: 2.7.2.0 +version: 2.7.2.1 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE From git at git.haskell.org Wed Jul 19 22:04:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:32 +0000 (UTC) Subject: [commit: packages/unix] bgamari-patch-1, master: Bump upper bound on base (245b6b1) Message-ID: <20170719220432.DE3133A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: bgamari-patch-1,master Link : http://ghc.haskell.org/trac/ghc/changeset/245b6b1c3f9161233235364a58e7c5914a354a57/unix >--------------------------------------------------------------- commit 245b6b1c3f9161233235364a58e7c5914a354a57 Author: Ben Gamari Date: Tue Nov 15 12:52:33 2016 -0500 Bump upper bound on base >--------------------------------------------------------------- 245b6b1c3f9161233235364a58e7c5914a354a57 unix.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/unix.cabal b/unix.cabal index 5ba2ddd..6565f1c 100644 --- a/unix.cabal +++ b/unix.cabal @@ -62,7 +62,7 @@ library buildable: False build-depends: - base >= 4.5 && < 4.10, + base >= 4.5 && < 4.11, bytestring >= 0.9.2 && < 0.11, time >= 1.2 && < 1.7 From git at git.haskell.org Wed Jul 19 22:04:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:36 +0000 (UTC) Subject: [commit: packages/unix] bgamari-patch-1, master: Relax upper bound on `time` to allow time-1.7 (97ced78) Message-ID: <20170719220436.EABF13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: bgamari-patch-1,master Link : http://ghc.haskell.org/trac/ghc/changeset/97ced7896688d1fc5bc72421229e3d0ff9b628dd/unix >--------------------------------------------------------------- commit 97ced7896688d1fc5bc72421229e3d0ff9b628dd Author: Herbert Valerio Riedel Date: Sun Nov 20 09:23:45 2016 +0100 Relax upper bound on `time` to allow time-1.7 ...after having convincing myself that the changes in time-1.7 are confined to parts not used by `unix` c.f. http://hdiff.luite.com/cgit/time/diff?id=1.7&id2=1.6.0.1 fixes #80 >--------------------------------------------------------------- 97ced7896688d1fc5bc72421229e3d0ff9b628dd unix.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/unix.cabal b/unix.cabal index 6565f1c..e31ecb4 100644 --- a/unix.cabal +++ b/unix.cabal @@ -64,7 +64,7 @@ library build-depends: base >= 4.5 && < 4.11, bytestring >= 0.9.2 && < 0.11, - time >= 1.2 && < 1.7 + time >= 1.2 && < 1.8 exposed-modules: System.Posix From git at git.haskell.org Wed Jul 19 22:04:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:38 +0000 (UTC) Subject: [commit: packages/unix] readdirstream-maybe-patch: Update readDirStream to use Maybe (7c89170) Message-ID: <20170719220438.F15303A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : readdirstream-maybe-patch Link : http://ghc.haskell.org/trac/ghc/changeset/7c89170c19db81b76fbcda8c73e6c6fd9f364f00/unix >--------------------------------------------------------------- commit 7c89170c19db81b76fbcda8c73e6c6fd9f364f00 Author: Eric Mertens Date: Tue Dec 6 23:22:53 2016 -0800 Update readDirStream to use Maybe This patch changes `readDirStream` to signal end of directory with a Nothing value. In addition it changes the wrapped readdir function to only return -1 in the case of an actual error. This change allows the errno handling logic to take advantage of helpers from Foreign.C.Error, simplifying the logic. Fixes #81 >--------------------------------------------------------------- 7c89170c19db81b76fbcda8c73e6c6fd9f364f00 System/Posix/Directory.hsc | 32 +++++++++++--------------------- System/Posix/Directory/ByteString.hsc | 32 +++++++++++--------------------- cbits/HsUnix.c | 3 ++- changelog.md | 4 ++++ 4 files changed, 28 insertions(+), 43 deletions(-) diff --git a/System/Posix/Directory.hsc b/System/Posix/Directory.hsc index 10dcbb4..7273f30 100644 --- a/System/Posix/Directory.hsc +++ b/System/Posix/Directory.hsc @@ -87,28 +87,18 @@ foreign import capi unsafe "HsUnix.h opendir" -- | @readDirStream dp@ calls @readdir@ to obtain the -- next directory entry (@struct dirent@) for the open directory -- stream @dp@, and returns the @d_name@ member of that --- structure. -readDirStream :: DirStream -> IO FilePath +-- structure. 'Nothing' is returned upon reaching the end +-- of the directory. +readDirStream :: DirStream -> IO (Maybe FilePath) readDirStream (DirStream dirp) = - alloca $ \ptr_dEnt -> loop ptr_dEnt - where - loop ptr_dEnt = do - resetErrno - r <- c_readdir dirp ptr_dEnt - if (r == 0) - then do dEnt <- peek ptr_dEnt - if (dEnt == nullPtr) - then return [] - else do - entry <- (d_name dEnt >>= peekFilePath) - c_freeDirEnt dEnt - return entry - else do errno <- getErrno - if (errno == eINTR) then loop ptr_dEnt else do - let (Errno eo) = errno - if (eo == 0) - then return [] - else throwErrno "readDirStream" + alloca $ \ptr_dEnt -> + do throwErrnoIfMinus1Retry_ "readdir" (c_readdir dirp ptr_dEnt) + dEnt <- peek ptr_dEnt + if dEnt == nullPtr + then return Nothing + else do entry <- peekFilePath =<< d_name dEnt + c_freeDirEnt dEnt + return (Just entry) -- traversing directories foreign import ccall unsafe "__hscore_readdir" diff --git a/System/Posix/Directory/ByteString.hsc b/System/Posix/Directory/ByteString.hsc index b5ea462..dc03212 100644 --- a/System/Posix/Directory/ByteString.hsc +++ b/System/Posix/Directory/ByteString.hsc @@ -88,28 +88,18 @@ foreign import capi unsafe "HsUnix.h opendir" -- | @readDirStream dp@ calls @readdir@ to obtain the -- next directory entry (@struct dirent@) for the open directory -- stream @dp@, and returns the @d_name@ member of that --- structure. -readDirStream :: DirStream -> IO RawFilePath +-- structure. 'Nothing' is returned upon reaching the end +-- of the directory. +readDirStream :: DirStream -> IO (Maybe RawFilePath) readDirStream (DirStream dirp) = - alloca $ \ptr_dEnt -> loop ptr_dEnt - where - loop ptr_dEnt = do - resetErrno - r <- c_readdir dirp ptr_dEnt - if (r == 0) - then do dEnt <- peek ptr_dEnt - if (dEnt == nullPtr) - then return BC.empty - else do - entry <- (d_name dEnt >>= peekFilePath) - c_freeDirEnt dEnt - return entry - else do errno <- getErrno - if (errno == eINTR) then loop ptr_dEnt else do - let (Errno eo) = errno - if (eo == 0) - then return BC.empty - else throwErrno "readDirStream" + alloca $ \ptr_dEnt -> + do throwErrnoIfMinus1Retry_ "readdir" (c_readdir dirp ptr_dEnt) + dEnt <- peek ptr_dEnt + if dEnt == nullPtr + then return Nothing + else do entry <- peekFilePath =<< d_name dEnt + c_freeDirEnt dEnt + return (Just entry) -- traversing directories foreign import ccall unsafe "__hscore_readdir" diff --git a/cbits/HsUnix.c b/cbits/HsUnix.c index 7c72a34..5ba9fdc 100644 --- a/cbits/HsUnix.c +++ b/cbits/HsUnix.c @@ -94,8 +94,9 @@ int __hscore_readdir( DIR *dirPtr, struct dirent **pDirEnt ) return -1; } + errno = 0; *pDirEnt = readdir(dirPtr); - if (*pDirEnt == NULL) { + if (*pDirEnt == NULL && errno != 0) { return -1; } else { return 0; diff --git a/changelog.md b/changelog.md index 4bbeeb3..d1bc198 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,9 @@ # Changelog for [`unix` package](http://hackage.haskell.org/package/unix) +## next + + * Change type of `readDirStream` and use `Nothing` to signal end of directory + ## 2.7.2.1 *Sep 2016* * Don't use `readdir_r` if its deprecated. From git at git.haskell.org Wed Jul 19 22:04:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:43 +0000 (UTC) Subject: [commit: packages/unix] bgamari-patch-1: Bump upper bound on time to allow 1.9 (adefe0c) Message-ID: <20170719220443.0A33D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : bgamari-patch-1 Link : http://ghc.haskell.org/trac/ghc/changeset/adefe0c3d715fe61bd57bede87ed8783c0af7f18/unix >--------------------------------------------------------------- commit adefe0c3d715fe61bd57bede87ed8783c0af7f18 Author: Ben Gamari Date: Thu Jan 19 16:19:32 2017 -0500 Bump upper bound on time to allow 1.9 >--------------------------------------------------------------- adefe0c3d715fe61bd57bede87ed8783c0af7f18 unix.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/unix.cabal b/unix.cabal index e31ecb4..c11be3f 100644 --- a/unix.cabal +++ b/unix.cabal @@ -64,7 +64,7 @@ library build-depends: base >= 4.5 && < 4.11, bytestring >= 0.9.2 && < 0.11, - time >= 1.2 && < 1.8 + time >= 1.2 && < 1.9 exposed-modules: System.Posix From git at git.haskell.org Wed Jul 19 22:04:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:34 +0000 (UTC) Subject: [commit: packages/unix] bgamari-patch-1, master: testsuite: Ensure that posix005 output is normalized (a3f6bc7) Message-ID: <20170719220434.E3E803A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: bgamari-patch-1,master Link : http://ghc.haskell.org/trac/ghc/changeset/a3f6bc7b7a18fb841c04efe0ea137096cc036764/unix >--------------------------------------------------------------- commit a3f6bc7b7a18fb841c04efe0ea137096cc036764 Author: Ben Gamari Date: Thu Nov 17 16:37:41 2016 -0500 testsuite: Ensure that posix005 output is normalized The order in which getEnvironment returns its result is platform dependent. Sort the output to ensure consistent output across platforms. >--------------------------------------------------------------- a3f6bc7b7a18fb841c04efe0ea137096cc036764 tests/libposix/posix005.hs | 15 +++++++++------ 1 file changed, 9 insertions(+), 6 deletions(-) diff --git a/tests/libposix/posix005.hs b/tests/libposix/posix005.hs index 4365eb5..2988f4c 100644 --- a/tests/libposix/posix005.hs +++ b/tests/libposix/posix005.hs @@ -2,20 +2,23 @@ import System.IO import System.Posix.Env +printEnv :: IO () +printEnv = getEnvironment >>= print . sort + main = do hSetBuffering stdout NoBuffering term <- getEnv "TERM" maybe (return ()) putStrLn term setEnvironment [("one","1"),("two","2")] - getEnvironment >>= print + printEnv setEnv "foo" "bar" True - getEnvironment >>= print + printEnv setEnv "foo" "baz" True - getEnvironment >>= print + printEnv setEnv "fu" "bar" True - getEnvironment >>= print + printEnv unsetEnv "foo" - getEnvironment >>= print + printEnv clearEnv - getEnvironment >>= print + printEnv From git at git.haskell.org Wed Jul 19 22:04:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:45 +0000 (UTC) Subject: [commit: packages/unix] master: Fix error message of `createSymbolicLink`. (fae5cdc) Message-ID: <20170719220445.10BC63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fae5cdc103edafb55ef86699dd9571f35b8cf8ed/unix >--------------------------------------------------------------- commit fae5cdc103edafb55ef86699dd9571f35b8cf8ed Author: Niklas Hambüchen Date: Wed Feb 8 03:09:00 2017 +0100 Fix error message of `createSymbolicLink`. Consider `ln` (or any other Unix tool): $ ln -s file1 file2 $ ls -l file2 lrwxrwxrwx 1 niklas niklas 5 Feb 8 03:09 file2 -> file1 $ ln -s file1 file2 ln: failed to create symbolic link 'file2': File exists The file name mentioned in the error ("link2") is the one that *could not be created*, not the content of the pointer. `createSymbolicLink` got this wrong so far, it would print file1: createSymbolicLink: already exists (File exists) which is wrong, this file doesn't already exist. This commit fixes it. >--------------------------------------------------------------- fae5cdc103edafb55ef86699dd9571f35b8cf8ed System/Posix/Files.hsc | 2 +- System/Posix/Files/ByteString.hsc | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/System/Posix/Files.hsc b/System/Posix/Files.hsc index bbda084..749f5da 100644 --- a/System/Posix/Files.hsc +++ b/System/Posix/Files.hsc @@ -253,7 +253,7 @@ createSymbolicLink :: FilePath -> FilePath -> IO () createSymbolicLink file1 file2 = withFilePath file1 $ \s1 -> withFilePath file2 $ \s2 -> - throwErrnoPathIfMinus1_ "createSymbolicLink" file1 (c_symlink s1 s2) + throwErrnoPathIfMinus1_ "createSymbolicLink" file2 (c_symlink s1 s2) foreign import ccall unsafe "symlink" c_symlink :: CString -> CString -> IO CInt diff --git a/System/Posix/Files/ByteString.hsc b/System/Posix/Files/ByteString.hsc index 872817e..23a44e3 100644 --- a/System/Posix/Files/ByteString.hsc +++ b/System/Posix/Files/ByteString.hsc @@ -259,7 +259,7 @@ createSymbolicLink :: RawFilePath -> RawFilePath -> IO () createSymbolicLink file1 file2 = withFilePath file1 $ \s1 -> withFilePath file2 $ \s2 -> - throwErrnoPathIfMinus1_ "createSymbolicLink" file1 (c_symlink s1 s2) + throwErrnoPathIfMinus1_ "createSymbolicLink" file2 (c_symlink s1 s2) foreign import ccall unsafe "symlink" c_symlink :: CString -> CString -> IO CInt From git at git.haskell.org Wed Jul 19 22:04:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:47 +0000 (UTC) Subject: [commit: packages/unix] master: Merge pull request #84 from nh2/fix-createSymbolicLink-exists-error-message (312ed21) Message-ID: <20170719220447.16C283A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/312ed2165d04b4c8db7b07133209f69b19b45745/unix >--------------------------------------------------------------- commit 312ed2165d04b4c8db7b07133209f69b19b45745 Merge: d0b0e8c fae5cdc Author: Eric Mertens Date: Mon Feb 13 17:07:40 2017 -0800 Merge pull request #84 from nh2/fix-createSymbolicLink-exists-error-message Fix error message of `createSymbolicLink`. >--------------------------------------------------------------- 312ed2165d04b4c8db7b07133209f69b19b45745 System/Posix/Files.hsc | 2 +- System/Posix/Files/ByteString.hsc | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) From git at git.haskell.org Wed Jul 19 22:04:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:41 +0000 (UTC) Subject: [commit: packages/unix] bgamari-patch-1, master: Fix posix005 test (d0b0e8c) Message-ID: <20170719220441.03AE93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: bgamari-patch-1,master Link : http://ghc.haskell.org/trac/ghc/changeset/d0b0e8cf5a7fa5b9dc500d2f623258200818cb16/unix >--------------------------------------------------------------- commit d0b0e8cf5a7fa5b9dc500d2f623258200818cb16 Author: Ben Gamari Date: Thu Dec 15 14:06:36 2016 -0500 Fix posix005 test Needed import of sort and updated expected output >--------------------------------------------------------------- d0b0e8cf5a7fa5b9dc500d2f623258200818cb16 tests/libposix/posix005.hs | 2 +- tests/libposix/posix005.stdout | 8 ++++---- 2 files changed, 5 insertions(+), 5 deletions(-) diff --git a/tests/libposix/posix005.hs b/tests/libposix/posix005.hs index 2988f4c..91331ff 100644 --- a/tests/libposix/posix005.hs +++ b/tests/libposix/posix005.hs @@ -1,4 +1,4 @@ - +import Data.List (sort) import System.IO import System.Posix.Env diff --git a/tests/libposix/posix005.stdout b/tests/libposix/posix005.stdout index ace79ee..4f60054 100644 --- a/tests/libposix/posix005.stdout +++ b/tests/libposix/posix005.stdout @@ -1,7 +1,7 @@ vt100 [("one","1"),("two","2")] -[("one","1"),("two","2"),("foo","bar")] -[("one","1"),("two","2"),("foo","baz")] -[("one","1"),("two","2"),("foo","baz"),("fu","bar")] -[("one","1"),("two","2"),("fu","bar")] +[("foo","bar"),("one","1"),("two","2")] +[("foo","baz"),("one","1"),("two","2")] +[("foo","baz"),("fu","bar"),("one","1"),("two","2")] +[("fu","bar"),("one","1"),("two","2")] [] From git at git.haskell.org Wed Jul 19 22:04:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:49 +0000 (UTC) Subject: [commit: packages/unix] master: Bump time upper bound (821cb07) Message-ID: <20170719220449.1C0E73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/821cb07ecf235625b4bb06626d30e4b15f28df30/unix >--------------------------------------------------------------- commit 821cb07ecf235625b4bb06626d30e4b15f28df30 Author: Ben Gamari Date: Mon Feb 20 16:50:59 2017 -0500 Bump time upper bound >--------------------------------------------------------------- 821cb07ecf235625b4bb06626d30e4b15f28df30 unix.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/unix.cabal b/unix.cabal index e31ecb4..c11be3f 100644 --- a/unix.cabal +++ b/unix.cabal @@ -64,7 +64,7 @@ library build-depends: base >= 4.5 && < 4.11, bytestring >= 0.9.2 && < 0.11, - time >= 1.2 && < 1.8 + time >= 1.2 && < 1.9 exposed-modules: System.Posix From git at git.haskell.org Wed Jul 19 22:04:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:51 +0000 (UTC) Subject: [commit: packages/unix] master: Merge pull request #89 from bgamari/master (a2cf40e) Message-ID: <20170719220451.24A313A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a2cf40ea8043c262a5a53a1e7f401def195df3a8/unix >--------------------------------------------------------------- commit a2cf40ea8043c262a5a53a1e7f401def195df3a8 Merge: 312ed21 821cb07 Author: Ben Gamari Date: Mon Feb 20 23:13:24 2017 +0000 Merge pull request #89 from bgamari/master Bump time upper bound >--------------------------------------------------------------- a2cf40ea8043c262a5a53a1e7f401def195df3a8 unix.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Wed Jul 19 22:04:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:53 +0000 (UTC) Subject: [commit: packages/unix] master: Define _POSIX_VDISABLE, if not defined. (d7aa9cd) Message-ID: <20170719220453.2B4453A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d7aa9cd00bbff62f1873e242ffe3f816c2fdc5b5/unix >--------------------------------------------------------------- commit d7aa9cd00bbff62f1873e242ffe3f816c2fdc5b5 Author: Moritz Angermann Date: Wed Mar 15 21:19:09 2017 +0800 Define _POSIX_VDISABLE, if not defined. >--------------------------------------------------------------- d7aa9cd00bbff62f1873e242ffe3f816c2fdc5b5 System/Posix/Terminal/Common.hsc | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/System/Posix/Terminal/Common.hsc b/System/Posix/Terminal/Common.hsc index 573df16..2773158 100644 --- a/System/Posix/Terminal/Common.hsc +++ b/System/Posix/Terminal/Common.hsc @@ -15,6 +15,12 @@ -- ----------------------------------------------------------------------------- +-- see https://android.googlesource.com/platform/bionic/+/9ae59c0/libc/bionic/pathconf.c#37 +#if !defined(_POSIX_VDISABLE) && defined(__ANDROID__) +#define _POSIX_VDISABLE -1 +#endif + + module System.Posix.Terminal.Common ( -- * Terminal support From git at git.haskell.org Wed Jul 19 22:04:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:55 +0000 (UTC) Subject: [commit: packages/unix] master: Merge pull request #90 from zw3rk/feature/android (47bcb47) Message-ID: <20170719220455.312E33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/47bcb4751c47e4026a7458f94e542d2c7dbbf92d/unix >--------------------------------------------------------------- commit 47bcb4751c47e4026a7458f94e542d2c7dbbf92d Merge: a2cf40e d7aa9cd Author: Ben Gamari Date: Wed Mar 15 09:33:21 2017 -0400 Merge pull request #90 from zw3rk/feature/android Define _POSIX_VDISABLE, if not defined. >--------------------------------------------------------------- 47bcb4751c47e4026a7458f94e542d2c7dbbf92d System/Posix/Terminal/Common.hsc | 6 ++++++ 1 file changed, 6 insertions(+) From git at git.haskell.org Wed Jul 19 22:04:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:57 +0000 (UTC) Subject: [commit: packages/unix] master: Android doesn’t have telldir/seekdir in bionic (540a317) Message-ID: <20170719220457.36FD73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/540a317a212ecef8592cc8089ecce1dacea08b2b/unix >--------------------------------------------------------------- commit 540a317a212ecef8592cc8089ecce1dacea08b2b Author: Moritz Angermann Date: Mon Mar 20 09:26:04 2017 +0800 Android doesn’t have telldir/seekdir in bionic The isse here is that while we try to use `AC_CHECK_FUNCS`, this will generate test code that tries to link an object and check for linking errors. However GNU gold at least version (binutils-2.25-0666073 2.25.51.20141117) 1.11, considers seekdir/telldir as part of the default libs. Thus we would actually want to pass `-nodefaultlibs` to the linker. Doing so, would result in erros due to not finding `-ldl`. Fixes #91 >--------------------------------------------------------------- 540a317a212ecef8592cc8089ecce1dacea08b2b configure.ac | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/configure.ac b/configure.ac index fdc27e4..32f7174 100644 --- a/configure.ac +++ b/configure.ac @@ -37,8 +37,10 @@ AC_CHECK_FUNCS([nanosleep]) AC_CHECK_FUNCS([ptsname]) AC_CHECK_FUNCS([setitimer]) AC_CHECK_FUNCS([readdir_r]) + dnl not available on android so check for it -AC_CHECK_FUNCS([telldir seekdir]) +AC_CANONICAL_TARGET +AS_CASE([$target_os],[*-android*],[],[AC_CHECK_FUNCS([telldir seekdir])]) dnl When available, _NSGetEnviron() (defined in ) is dnl the preferred way to access environ(7) From git at git.haskell.org Wed Jul 19 22:04:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:04:59 +0000 (UTC) Subject: [commit: packages/unix] master: Merge pull request #92 from zw3rk/feature/seekdir (19aaa0f) Message-ID: <20170719220459.3D9E13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/19aaa0fcca3427e4006a967972eb16a570ca43b1/unix >--------------------------------------------------------------- commit 19aaa0fcca3427e4006a967972eb16a570ca43b1 Merge: 47bcb47 540a317 Author: Herbert Valerio Riedel Date: Mon Mar 20 09:14:45 2017 +0100 Merge pull request #92 from zw3rk/feature/seekdir Android doesn’t have telldir/seekdir in bionic >--------------------------------------------------------------- 19aaa0fcca3427e4006a967972eb16a570ca43b1 configure.ac | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) From git at git.haskell.org Wed Jul 19 22:05:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:03 +0000 (UTC) Subject: [commit: packages/unix] master: Update config.{guess,sub} (9c2df12) Message-ID: <20170719220503.4CE7F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9c2df120b2d6c8178d6cbef31bdcba3b574934be/unix >--------------------------------------------------------------- commit 9c2df120b2d6c8178d6cbef31bdcba3b574934be Author: Moritz Angermann Date: Tue May 9 15:54:58 2017 +0800 Update config.{guess,sub} Autoconf hasn’t had an update since 2014, and it doesn’t look like it will soon[1] This updates config.{guess,sub} It basically does exactly what the config.guess script says: > It is advised that you download the most up to date version of the config scripts from It adds support for e.g. `-ios`, which allows to have targets like `aarch64-apple-ios`. — [1]: http://lists.gnu.org/archive/html/autoconf/2016-07/msg00017.html >--------------------------------------------------------------- 9c2df120b2d6c8178d6cbef31bdcba3b574934be config.guess | 184 +++++++++++++++++++++++++++++++++++++---------------------- config.sub | 90 +++++++++++++++++++++-------- 2 files changed, 181 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 9c2df120b2d6c8178d6cbef31bdcba3b574934be From git at git.haskell.org Wed Jul 19 22:05:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:01 +0000 (UTC) Subject: [commit: packages/unix] master: Update changelog and increment package version (db8be85) Message-ID: <20170719220501.447F73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/db8be857ba0d1e25e8d30c53ea7338cb9929b9b4/unix >--------------------------------------------------------------- commit db8be857ba0d1e25e8d30c53ea7338cb9929b9b4 Author: Herbert Valerio Riedel Date: Mon May 1 00:10:28 2017 +0200 Update changelog and increment package version >--------------------------------------------------------------- db8be857ba0d1e25e8d30c53ea7338cb9929b9b4 changelog.md | 11 +++++++++++ unix.cabal | 2 +- 2 files changed, 12 insertions(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index c773d3d..cb8003f 100644 --- a/changelog.md +++ b/changelog.md @@ -1,7 +1,18 @@ # Changelog for [`unix` package](http://hackage.haskell.org/package/unix) +## 2.7.2.2 *May 2017* + + * Bundled with GHC 8.2.1 + + * Improve Autoconf detection of `telldir`/`seekdir` and define + `_POSIX_VDISABLE` if missing for Android (#91,#90) + + * Fix error message of `createSymbolicLink` (#84) + ## 2.7.2.1 *Nov 2016* + * Bundled with GHC 8.0.2 + * Don't use `readdir_r` if its deprecated. * Add argument documentation for Env modules diff --git a/unix.cabal b/unix.cabal index c11be3f..cf44068 100644 --- a/unix.cabal +++ b/unix.cabal @@ -1,5 +1,5 @@ name: unix -version: 2.7.2.1 +version: 2.7.2.2 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE From git at git.haskell.org Wed Jul 19 22:05:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:07 +0000 (UTC) Subject: [commit: packages/unix] master: Android doesn’t have mkstemps (b5b6253) Message-ID: <20170719220507.5A36F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b5b62536e80344db4468d12fc6ded9fb4bc52be0/unix >--------------------------------------------------------------- commit b5b62536e80344db4468d12fc6ded9fb4bc52be0 Author: Moritz Angermann Date: Tue May 9 15:49:43 2017 +0800 Android doesn’t have mkstemps However the check similarly to tell and seekdir succeeds. However we will generate the following error down the line: ``` /var/folders/fv/xqjrpfj516n5xq_m_ljpsjx00000gn/T/ghc13524_0/ghc_2.c:11:104: error: warning: implicit declaration of function 'mkstemps' is invalid in C99 [-Wimplicit-function-declaration] | 11 | HsInt32 ghczuwrapperZC1ZCunixzm2zi7zi2zi1ZCSystemziPosixziTempZCmkstemps(void* a1, HsInt32 a2) {return mkstemps(a1, a2);} | ^ HsInt32 ghczuwrapperZC1ZCunixzm2zi7zi2zi1ZCSystemziPosixziTempZCmkstemps(void* a1, HsInt32 a2) {return mkstemps(a1, a2);} ^ ``` >--------------------------------------------------------------- b5b62536e80344db4468d12fc6ded9fb4bc52be0 configure.ac | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/configure.ac b/configure.ac index 32f7174..b23caef 100644 --- a/configure.ac +++ b/configure.ac @@ -73,7 +73,8 @@ AC_CHECK_FUNCS([utimensat futimens]) AC_CHECK_FUNCS([lutimes futimes]) # Additional temp functions -AC_CHECK_FUNCS([mkstemps mkdtemp]) +dnl androids bionic doesn't have mkstemps +AS_CASE([$target_os],[*-android*],[AC_CHECK_FUNCS([mkdtemp])],[AC_CHECK_FUNCS([mkstemps mkdtemp])]) # Functions for file synchronization and allocation control AC_CHECK_FUNCS([fsync]) From git at git.haskell.org Wed Jul 19 22:05:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:05 +0000 (UTC) Subject: [commit: packages/unix] master: Update configure.ac (eb5fc94) Message-ID: <20170719220505.544663A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eb5fc942f8f570e754bba0f57a8fdaec3400194f/unix >--------------------------------------------------------------- commit eb5fc942f8f570e754bba0f57a8fdaec3400194f Author: Moritz Angermann Date: Thu May 11 09:44:20 2017 +0800 Update configure.ac Add Comment >--------------------------------------------------------------- eb5fc942f8f570e754bba0f57a8fdaec3400194f configure.ac | 2 ++ 1 file changed, 2 insertions(+) diff --git a/configure.ac b/configure.ac index b23caef..c23c9e1 100644 --- a/configure.ac +++ b/configure.ac @@ -74,6 +74,8 @@ AC_CHECK_FUNCS([lutimes futimes]) # Additional temp functions dnl androids bionic doesn't have mkstemps +# We explicilty check for android, as the check AC_CHECK_FUNCS performs returns "yes" for mkstemps +# when targetting android. See similar conditionals for seekdir and telldir. AS_CASE([$target_os],[*-android*],[AC_CHECK_FUNCS([mkdtemp])],[AC_CHECK_FUNCS([mkstemps mkdtemp])]) # Functions for file synchronization and allocation control From git at git.haskell.org Wed Jul 19 22:05:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:09 +0000 (UTC) Subject: [commit: packages/unix] master: gitignore cabal sandbox and new-build artifacts (e9fd857) Message-ID: <20170719220509.5FFDB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e9fd857724a8d27afe11d8dbbfeaaabcac48b282/unix >--------------------------------------------------------------- commit e9fd857724a8d27afe11d8dbbfeaaabcac48b282 Author: George Wilson Date: Thu Jun 22 13:52:22 2017 +1000 gitignore cabal sandbox and new-build artifacts >--------------------------------------------------------------- e9fd857724a8d27afe11d8dbbfeaaabcac48b282 .gitignore | 3 +++ 1 file changed, 3 insertions(+) diff --git a/.gitignore b/.gitignore index 6879b90..7606fc9 100644 --- a/.gitignore +++ b/.gitignore @@ -1,6 +1,9 @@ # Specific generated files GNUmakefile autom4te.cache/ +.cabal-sandbox/ +cabal.project.local +cabal.sandbox.config config.log config.status configure From git at git.haskell.org Wed Jul 19 22:05:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:13 +0000 (UTC) Subject: [commit: packages/unix] master: .ghc.environment has a leading dot (dc22ed7) Message-ID: <20170719220513.6BDB13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dc22ed7fee05d9f00b68d9e1628561a225af32ba/unix >--------------------------------------------------------------- commit dc22ed7fee05d9f00b68d9e1628561a225af32ba Author: Eric Mertens Date: Thu Jun 22 17:02:36 2017 -0700 .ghc.environment has a leading dot >--------------------------------------------------------------- dc22ed7fee05d9f00b68d9e1628561a225af32ba .gitignore | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitignore b/.gitignore index ae0afc1..c52a0a2 100644 --- a/.gitignore +++ b/.gitignore @@ -10,7 +10,7 @@ configure dist/ dist-install/ dist-newstyle/ -ghc.environment.* +.ghc.environment.* ghc.mk include/HsUnixConfig.h include/HsUnixConfig.h.in From git at git.haskell.org Wed Jul 19 22:05:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:11 +0000 (UTC) Subject: [commit: packages/unix] master: Ignore ghc.environment.* too (5903e67) Message-ID: <20170719220511.665433A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5903e67016dadddc52a62d54efdc00fe505ed018/unix >--------------------------------------------------------------- commit 5903e67016dadddc52a62d54efdc00fe505ed018 Author: George Wilson Date: Fri Jun 23 07:54:41 2017 +1000 Ignore ghc.environment.* too >--------------------------------------------------------------- 5903e67016dadddc52a62d54efdc00fe505ed018 .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index 7606fc9..ae0afc1 100644 --- a/.gitignore +++ b/.gitignore @@ -10,6 +10,7 @@ configure dist/ dist-install/ dist-newstyle/ +ghc.environment.* ghc.mk include/HsUnixConfig.h include/HsUnixConfig.h.in From git at git.haskell.org Wed Jul 19 22:05:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:39 +0000 (UTC) Subject: [commit: packages/time] tag '1.8.0.2' created Message-ID: <20170719220539.957613A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time New tag : 1.8.0.2 Referencing: 7184831d3242ef49d1c44b52c9ecaa7dd1c83efc From git at git.haskell.org Wed Jul 19 22:05:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:15 +0000 (UTC) Subject: [commit: packages/unix] master: Merge pull request #97 from gwils/gitignore-cabal-sandbox-newbuild (fcaa530) Message-ID: <20170719220515.720FC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fcaa530a8fdd3897353bdf246752a91d675aad46/unix >--------------------------------------------------------------- commit fcaa530a8fdd3897353bdf246752a91d675aad46 Merge: eb5fc94 dc22ed7 Author: Eric Mertens Date: Thu Jun 22 17:03:47 2017 -0700 Merge pull request #97 from gwils/gitignore-cabal-sandbox-newbuild gitignore cabal sandbox and new-build artifacts >--------------------------------------------------------------- fcaa530a8fdd3897353bdf246752a91d675aad46 .gitignore | 4 ++++ 1 file changed, 4 insertions(+) From git at git.haskell.org Wed Jul 19 22:05:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:41 +0000 (UTC) Subject: [commit: packages/time] ghc,master: Fix #ifdef (05776df) Message-ID: <20170719220541.9D6053A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branches: ghc,master Link : http://git.haskell.org/packages/time.git/commitdiff/05776dfaa74cdccbaa80ecdf7dd6fe48e9ae203b >--------------------------------------------------------------- commit 05776dfaa74cdccbaa80ecdf7dd6fe48e9ae203b Author: Ben Gamari Date: Sun Apr 30 08:48:25 2017 -0400 Fix #ifdef GHC is now compiled with -Werror=undef; explicitly use #ifdef instead of #if >--------------------------------------------------------------- 05776dfaa74cdccbaa80ecdf7dd6fe48e9ae203b lib/Data/Time/Clock/Internal/SystemTime.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/lib/Data/Time/Clock/Internal/SystemTime.hs b/lib/Data/Time/Clock/Internal/SystemTime.hs index 6027cdf..b87d302 100644 --- a/lib/Data/Time/Clock/Internal/SystemTime.hs +++ b/lib/Data/Time/Clock/Internal/SystemTime.hs @@ -19,7 +19,7 @@ import Data.Time.Clock.Internal.DiffTime #ifdef mingw32_HOST_OS import qualified System.Win32.Time as Win32 -#elif HAVE_CLOCK_GETTIME +#elif defined(HAVE_CLOCK_GETTIME) import Data.Time.Clock.Internal.CTimespec import Foreign.C.Types (CTime(..), CLong(..)) #else @@ -67,7 +67,7 @@ getSystemTime = do getTime_resolution = 100E-9 -- 100ns getTAISystemTime = Nothing -#elif HAVE_CLOCK_GETTIME +#elif defined(HAVE_CLOCK_GETTIME) -- Use hi-res clock_gettime timespecToSystemTime :: CTimespec -> SystemTime From git at git.haskell.org Wed Jul 19 22:05:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:43 +0000 (UTC) Subject: [commit: packages/time] ghc, master: Merge pull request #73 from bgamari/master (699ab28) Message-ID: <20170719220543.A4A2E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branches: ghc,master Link : http://git.haskell.org/packages/time.git/commitdiff/699ab286eefc63148eef5c18294868e937b036d5 >--------------------------------------------------------------- commit 699ab286eefc63148eef5c18294868e937b036d5 Merge: fbf90b6 05776df Author: Ashley Yakeley Date: Sun Apr 30 22:53:26 2017 -0700 Merge pull request #73 from bgamari/master Fix #ifdef >--------------------------------------------------------------- 699ab286eefc63148eef5c18294868e937b036d5 From git at git.haskell.org Wed Jul 19 22:05:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:45 +0000 (UTC) Subject: [commit: packages/time] ghc, master: fix format behaviour of %Q (c29513e) Message-ID: <20170719220545.AC5E73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branches: ghc,master Link : http://git.haskell.org/packages/time.git/commitdiff/c29513e6f79f6f8cefc69663c34e780570bef34a >--------------------------------------------------------------- commit c29513e6f79f6f8cefc69663c34e780570bef34a Author: Ashley Yakeley Date: Sat May 13 03:36:21 2017 -0700 fix format behaviour of %Q >--------------------------------------------------------------- c29513e6f79f6f8cefc69663c34e780570bef34a lib/Data/Time/Format.hs | 4 +++- test/unix/Test/Format/Format.hs | 4 ++-- 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/lib/Data/Time/Format.hs b/lib/Data/Time/Format.hs index bb03e24..efbb43f 100644 --- a/lib/Data/Time/Format.hs +++ b/lib/Data/Time/Format.hs @@ -275,7 +275,9 @@ instance FormatTime TimeOfDay where -- Second formatCharacter 'S' = Just $ padNum True 2 '0' $ (floor . todSec :: TimeOfDay -> Int) formatCharacter 'q' = Just $ padGeneral True True 12 '0' $ \_ pado -> showPaddedFixedFraction pado . todSec - formatCharacter 'Q' = Just $ padGeneral True False 12 '0' $ \_ pado -> ('.':) . showPaddedFixedFraction pado . todSec + formatCharacter 'Q' = Just $ padGeneral True False 12 '0' $ \_ pado -> dotNonEmpty . showPaddedFixedFraction pado . todSec where + dotNonEmpty "" = "" + dotNonEmpty s = '.':s -- Default formatCharacter _ = Nothing diff --git a/test/unix/Test/Format/Format.hs b/test/unix/Test/Format/Format.hs index fa7d5b8..7a816f0 100644 --- a/test/unix/Test/Format/Format.hs +++ b/test/unix/Test/Format/Format.hs @@ -190,13 +190,13 @@ testQs = [ formatUnitTest "%-5q" 0 " ", formatUnitTest "%-5q" 0.37 "37 ", - formatUnitTest "%Q" 0 ".", + formatUnitTest "%Q" 0 "", formatUnitTest "%Q" 0.37 ".37", formatUnitTest "%0Q" 0 ".000000000000", formatUnitTest "%0Q" 0.37 ".370000000000", formatUnitTest "%_Q" 0 ". ", formatUnitTest "%_Q" 0.37 ".37 ", - formatUnitTest "%-Q" 0 ".", + formatUnitTest "%-Q" 0 "", formatUnitTest "%-Q" 0.37 ".37", formatUnitTest "%1Q" 0 ".0", formatUnitTest "%1Q" 0.37 ".3", From git at git.haskell.org Wed Jul 19 22:05:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:47 +0000 (UTC) Subject: [commit: packages/time] ghc, master: Merge branch 'master' of github.com:haskell/time (9539368) Message-ID: <20170719220547.B3B673A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branches: ghc,master Link : http://git.haskell.org/packages/time.git/commitdiff/953936893809bcd66761e14c76c2a653a77dfa58 >--------------------------------------------------------------- commit 953936893809bcd66761e14c76c2a653a77dfa58 Merge: c29513e 699ab28 Author: Ashley Yakeley Date: Sat May 13 03:36:34 2017 -0700 Merge branch 'master' of github.com:haskell/time >--------------------------------------------------------------- 953936893809bcd66761e14c76c2a653a77dfa58 lib/Data/Time/Clock/Internal/SystemTime.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) From git at git.haskell.org Wed Jul 19 22:05:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:49 +0000 (UTC) Subject: [commit: packages/time] ghc, master: Format: update comment on %Q specifier (2a09e11) Message-ID: <20170719220549.BB29E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branches: ghc,master Link : http://git.haskell.org/packages/time.git/commitdiff/2a09e11ff877ab7e282e926bab73df858082017c >--------------------------------------------------------------- commit 2a09e11ff877ab7e282e926bab73df858082017c Author: Ashley Yakeley Date: Sat May 13 12:23:28 2017 -0700 Format: update comment on %Q specifier >--------------------------------------------------------------- 2a09e11ff877ab7e282e926bab73df858082017c lib/Data/Time/Format.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/Data/Time/Format.hs b/lib/Data/Time/Format.hs index efbb43f..6d08371 100644 --- a/lib/Data/Time/Format.hs +++ b/lib/Data/Time/Format.hs @@ -143,7 +143,7 @@ formatChar c = case formatCharacter c of -- [@%q@] picosecond of second, 0-padded to twelve chars, @000000000000@ - @999999999999 at . -- -- [@%Q@] decimal point and fraction of second, up to 12 second decimals, without trailing zeros. --- For a whole number of seconds, @%Q@ produces the empty string. +-- For a whole number of seconds, @%Q@ omits the decimal point unless padding is specified. -- -- === 'UTCTime' and 'ZonedTime' -- For 'UTCTime' and 'ZonedTime': From git at git.haskell.org Wed Jul 19 22:05:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:51 +0000 (UTC) Subject: [commit: packages/time] ghc,master: version 1.8.0.2 (e7e07a6) Message-ID: <20170719220551.C252F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branches: ghc,master Link : http://git.haskell.org/packages/time.git/commitdiff/e7e07a6c12b1e0dea221cc6f4ed10ce4848044fe >--------------------------------------------------------------- commit e7e07a6c12b1e0dea221cc6f4ed10ce4848044fe Author: Ashley Yakeley Date: Sat May 13 13:00:07 2017 -0700 version 1.8.0.2 >--------------------------------------------------------------- e7e07a6c12b1e0dea221cc6f4ed10ce4848044fe changelog.md | 3 +++ configure.ac | 2 +- time.cabal | 2 +- 3 files changed, 5 insertions(+), 2 deletions(-) diff --git a/changelog.md b/changelog.md index 9852afe..310be6a 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,8 @@ # Change Log +## [1.8.0.2] +- Fix behaviour of %Q in format + ## [1.8.0.1] - Get building on 32 bit machine diff --git a/configure.ac b/configure.ac index 8baf740..f415bfc 100644 --- a/configure.ac +++ b/configure.ac @@ -1,4 +1,4 @@ -AC_INIT([Haskell time package], [1.8.0.1], [ashley at semantic.org], [time]) +AC_INIT([Haskell time package], [1.8.0.2], [ashley at semantic.org], [time]) # Safety check: Ensure that we are in the correct source directory. AC_CONFIG_SRCDIR([lib/include/HsTime.h]) diff --git a/time.cabal b/time.cabal index e93c857..d1934fc 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.8.0.1 +version: 1.8.0.2 stability: stable license: BSD3 license-file: LICENSE From git at git.haskell.org Wed Jul 19 22:05:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:53 +0000 (UTC) Subject: [commit: packages/time] ghc, master: stack.yaml: updated to latest resolver (6f10527) Message-ID: <20170719220553.C8EA83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branches: ghc,master Link : http://git.haskell.org/packages/time.git/commitdiff/6f105272dc663a138886afe8dba4a871e2bed3c4 >--------------------------------------------------------------- commit 6f105272dc663a138886afe8dba4a871e2bed3c4 Author: Ashley Yakeley Date: Sat May 13 13:01:57 2017 -0700 stack.yaml: updated to latest resolver >--------------------------------------------------------------- 6f105272dc663a138886afe8dba4a871e2bed3c4 stack.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/stack.yaml b/stack.yaml index 819c851..856efd4 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,4 +1,4 @@ -resolver: lts-8.4 +resolver: lts-8.13 packages: - '.' allow-newer: true From git at git.haskell.org Wed Jul 19 22:05:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:55 +0000 (UTC) Subject: [commit: packages/time] ghc, master: Travis: GHC 8.0.2 build (1fcaa07) Message-ID: <20170719220555.D11F03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branches: ghc,master Link : http://git.haskell.org/packages/time.git/commitdiff/1fcaa07e10d7966356373ed0e946eb078fcdd6e6 >--------------------------------------------------------------- commit 1fcaa07e10d7966356373ed0e946eb078fcdd6e6 Author: Ashley Yakeley Date: Sat May 13 13:25:51 2017 -0700 Travis: GHC 8.0.2 build >--------------------------------------------------------------- 1fcaa07e10d7966356373ed0e946eb078fcdd6e6 .travis.yml | 3 +++ Checklist | 1 + 2 files changed, 4 insertions(+) diff --git a/.travis.yml b/.travis.yml index 4153c83..a6acdde 100644 --- a/.travis.yml +++ b/.travis.yml @@ -21,6 +21,9 @@ matrix: - env: CABALVER=1.24 GHCVER=8.0.1 compiler: ": #GHC 8.0.1" addons: {apt: {packages: [cabal-install-1.24,ghc-8.0.1], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=8.0.2 + compiler: ": #GHC 8.0.2" + addons: {apt: {packages: [cabal-install-1.24,ghc-8.0.2], sources: [hvr-ghc]}} before_install: - unset CC diff --git a/Checklist b/Checklist index 8fef7e8..c319dc6 100644 --- a/Checklist +++ b/Checklist @@ -20,6 +20,7 @@ Before release: https://www.stackage.org/lts stack.yaml (not necessarily benchmark/stack.yaml) + .travis.yml 5. Build & test From git at git.haskell.org Wed Jul 19 22:05:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:05:57 +0000 (UTC) Subject: [commit: packages/time] ghc's head updated: Travis: GHC 8.0.2 build (1fcaa07) Message-ID: <20170719220557.DED4E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time Branch 'ghc' now includes: d9e3430 test using "#ifdef" for HAVE_CLOCK_GETTIME fbf90b6 Merge pull request #71 from bgamari/master 05776df Fix #ifdef 699ab28 Merge pull request #73 from bgamari/master c29513e fix format behaviour of %Q 9539368 Merge branch 'master' of github.com:haskell/time 2a09e11 Format: update comment on %Q specifier e7e07a6 version 1.8.0.2 6f10527 stack.yaml: updated to latest resolver 1fcaa07 Travis: GHC 8.0.2 build From git at git.haskell.org Wed Jul 19 22:06:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:06:23 +0000 (UTC) Subject: [commit: packages/xhtml] tag '3000.2.0.4' created Message-ID: <20170719220623.06D343A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/xhtml New tag : 3000.2.0.4 Referencing: b5c197f7b5df3371aca74cc952120650fe115bcb From git at git.haskell.org Wed Jul 19 22:06:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:06:30 +0000 (UTC) Subject: [commit: packages/xhtml] tag '3000.2.0.5' created Message-ID: <20170719220630.13A583A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/xhtml New tag : 3000.2.0.5 Referencing: bb295a38a766c51db9f0817f3b10a97624d29be2 From git at git.haskell.org Wed Jul 19 22:06:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 22:06:32 +0000 (UTC) Subject: [commit: packages/xhtml] : 3000.2.0.5 from hackage (20ccd30) Message-ID: <20170719220632.198553A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/xhtml On branch : Link : http://git.haskell.org/packages/xhtml.git/commitdiff/20ccd30adca7b3b19566e3299607c35589d9fb34 >--------------------------------------------------------------- commit 20ccd30adca7b3b19566e3299607c35589d9fb34 Author: Chris Dornan Date: Wed May 23 09:13:45 2012 +0100 3000.2.0.5 from hackage >--------------------------------------------------------------- 20ccd30adca7b3b19566e3299607c35589d9fb34 .gitignore | 1 - xhtml.cabal | 2 +- 2 files changed, 1 insertion(+), 2 deletions(-) diff --git a/.gitignore b/.gitignore index 0e2ed13..3a4edf6 100644 --- a/.gitignore +++ b/.gitignore @@ -1,2 +1 @@ .project -dist diff --git a/xhtml.cabal b/xhtml.cabal index 72a4d1c..3f821d6 100644 --- a/xhtml.cabal +++ b/xhtml.cabal @@ -18,7 +18,7 @@ Cabal-version: >= 1.6 Source-repository head type: git - location: https://github.com/haskell/xhtml + location: git at github.com:haskell/xhtml.git library Build-depends: base >= 4.0 && < 5.0 From git at git.haskell.org Wed Jul 19 23:23:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:23:53 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: ghc.mk: Ensure that ghc-pkg path is quoted (c5a4b7c) Message-ID: <20170719232353.848F03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/c5a4b7c7e8e15fd6f26f54348473701190383e4f/ghc >--------------------------------------------------------------- commit c5a4b7c7e8e15fd6f26f54348473701190383e4f Author: Ben Gamari Date: Fri Jun 2 13:15:52 2017 -0400 ghc.mk: Ensure that ghc-pkg path is quoted Otherwise this will fail if the prefix path contains spaces. Thanks to marinelli for pointing this out. Test Plan: Validate Reviewers: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3604 (cherry picked from commit ff363bd74c8b2505b92b39d5fedcf95b8ab7365a) >--------------------------------------------------------------- c5a4b7c7e8e15fd6f26f54348473701190383e4f ghc.mk | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.mk b/ghc.mk index 004ac4a..0466164 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1020,7 +1020,7 @@ install_packages: rts/dist/package.conf.install # 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 + "$(INSTALLED_GHC_PKG_REAL)" --global-package-db "$(INSTALLED_PACKAGE_CONF)" recache # ----------------------------------------------------------------------------- # Binary distributions From git at git.haskell.org Wed Jul 19 23:23:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:23:56 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Update changelogs for 8.2.1 (2600a65) Message-ID: <20170719232356.3B9793A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/2600a65adf931857c5d18a7d1ab3529286ee9e99/ghc >--------------------------------------------------------------- commit 2600a65adf931857c5d18a7d1ab3529286ee9e99 Author: Ben Gamari Date: Tue Jul 11 14:05:10 2017 -0400 Update changelogs for 8.2.1 >--------------------------------------------------------------- 2600a65adf931857c5d18a7d1ab3529286ee9e99 libraries/base/changelog.md | 4 ++-- libraries/integer-gmp/changelog.md | 4 +++- libraries/template-haskell/changelog.md | 4 ++-- 3 files changed, 7 insertions(+), 5 deletions(-) diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 97fdefd..8cc955a 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -1,7 +1,7 @@ # Changelog for [`base` package](http://hackage.haskell.org/package/base) -## 4.10.0.0 *April 2017* - * Bundled with GHC *TBA* +## 4.10.0.0 *July 2017* + * Bundled with GHC 8.2.1 * `Data.Type.Bool.Not` given a type family dependency (#12057). diff --git a/libraries/integer-gmp/changelog.md b/libraries/integer-gmp/changelog.md index cdee847..3100349 100644 --- a/libraries/integer-gmp/changelog.md +++ b/libraries/integer-gmp/changelog.md @@ -1,6 +1,8 @@ # Changelog for [`integer-gmp` package](http://hackage.haskell.org/package/integer-gmp) -## 1.0.0.2 *TBA* +## 1.0.0.2 *July 2017* + + * Bundled with GHC 8.2.1 * Optimize `minusInteger` diff --git a/libraries/template-haskell/changelog.md b/libraries/template-haskell/changelog.md index 50f1709..c79cf99 100644 --- a/libraries/template-haskell/changelog.md +++ b/libraries/template-haskell/changelog.md @@ -1,8 +1,8 @@ # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell) -## 2.12.0.0 *TBA* +## 2.12.0.0 *July 2017* - * Bundled with GHC *TBA* + * Bundled with GHC 8.2.1. * Add support for pattern synonyms. This introduces one new constructor to `Info` (`PatSynI`), two new constructors to `Dec` (`PatSynD` and From git at git.haskell.org Wed Jul 19 23:23:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:23:58 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: StgLint: Don't loop on tycons with runtime rep arguments (ad49958) Message-ID: <20170719232358.E82743A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/ad49958c3b9328ef89535cc2f38026d6601a44c5/ghc >--------------------------------------------------------------- commit ad49958c3b9328ef89535cc2f38026d6601a44c5 Author: Ben Gamari Date: Tue Jul 11 14:43:19 2017 -0400 StgLint: Don't loop on tycons with runtime rep arguments Test Plan: Validate Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #13941 Differential Revision: https://phabricator.haskell.org/D3714 (cherry picked from commit be04c16b0e5fe9d50562e0868b890b0f9b778a41) >--------------------------------------------------------------- ad49958c3b9328ef89535cc2f38026d6601a44c5 compiler/stgSyn/StgLint.hs | 25 +++++++++++++++++++------ 1 file changed, 19 insertions(+), 6 deletions(-) diff --git a/compiler/stgSyn/StgLint.hs b/compiler/stgSyn/StgLint.hs index 02d989c..0362e15 100644 --- a/compiler/stgSyn/StgLint.hs +++ b/compiler/stgSyn/StgLint.hs @@ -27,7 +27,6 @@ import Util import SrcLoc import Outputable import Control.Monad -import Data.Function #include "HsVersions.h" @@ -419,18 +418,32 @@ stgEqType :: Type -> Type -> Bool -- Fundamentally this is a losing battle because of unsafeCoerce stgEqType orig_ty1 orig_ty2 - = gos (typePrimRep orig_ty1) (typePrimRep orig_ty2) + = gos orig_ty1 orig_ty2 where - gos :: [PrimRep] -> [PrimRep] -> Bool - gos [_] [_] = go orig_ty1 orig_ty2 - gos reps1 reps2 = reps1 == reps2 + gos :: Type -> Type -> Bool + gos ty1 ty2 + -- These have no prim rep + | isRuntimeRepKindedTy ty1 && isRuntimeRepKindedTy ty2 + = True + + -- We have a unary type + | [_] <- reps1, [_] <- reps2 + = go ty1 ty2 + + -- In the case of a tuple just compare prim reps + | otherwise + = reps1 == reps2 + where + reps1 = typePrimRep ty1 + reps2 = typePrimRep ty2 go :: UnaryType -> UnaryType -> Bool go ty1 ty2 | Just (tc1, tc_args1) <- splitTyConApp_maybe ty1 , Just (tc2, tc_args2) <- splitTyConApp_maybe ty2 , let res = if tc1 == tc2 - then equalLength tc_args1 tc_args2 && and (zipWith (gos `on` typePrimRep) tc_args1 tc_args2) + then equalLength tc_args1 tc_args2 + && and (zipWith gos tc_args1 tc_args2) else -- TyCons don't match; but don't bleat if either is a -- family TyCon because a coercion might have made it -- equal to something else From git at git.haskell.org Wed Jul 19 23:24:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:24:07 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix #13948 by being pickier about when to suggest DataKinds (fb46561) Message-ID: <20170719232407.3BEA43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/fb46561900480b8d9659ab3e9f8590a9a38a69ea/ghc >--------------------------------------------------------------- commit fb46561900480b8d9659ab3e9f8590a9a38a69ea Author: Ryan Scott Date: Tue Jul 11 13:59:07 2017 -0400 Fix #13948 by being pickier about when to suggest DataKinds Commit 343cb32d0983f576d344a2d04a35c3fd6eecf2c5 (#13568) made GHC a bit too cavalier in suggesting when data constructors are in scope (and suggesting the use of `DataKinds`). This tones down the suggestions so that `DataKinds` is only suggested if a data constructor of that name is actually in scope (previously, it would always suggest, even if it was out of scope). Fixes #13948. Test Plan: ./validate Reviewers: mpickering, austin, bgamari Reviewed By: mpickering Subscribers: rwbarton, thomie GHC Trac Issues: #13948 Differential Revision: https://phabricator.haskell.org/D3719 (cherry picked from commit ba46e63f3d6f7d0438a0262f6711f8a219c703bc) >--------------------------------------------------------------- fb46561900480b8d9659ab3e9f8590a9a38a69ea compiler/rename/RnEnv.hs | 11 ++++++++++- 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 +--- testsuite/tests/parser/should_fail/readFail001.stderr | 1 - testsuite/tests/rename/prog003/rename.prog003.stderr | 4 +--- testsuite/tests/rename/should_fail/T1595a.stderr | 1 - testsuite/tests/rename/should_fail/T5745.stderr | 4 +--- testsuite/tests/typecheck/should_fail/T1595.stderr | 2 -- testsuite/tests/typecheck/should_fail/tcfail048.stderr | 1 - testsuite/tests/typecheck/should_fail/tcfail053.stderr | 1 - 14 files changed, 15 insertions(+), 25 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fb46561900480b8d9659ab3e9f8590a9a38a69ea From git at git.haskell.org Wed Jul 19 23:24:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:24:01 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Clean up release notes (b6146d2) Message-ID: <20170719232401.B14363A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/b6146d284866d7d1b0a9370759054401c1303b1f/ghc >--------------------------------------------------------------- commit b6146d284866d7d1b0a9370759054401c1303b1f Author: Ben Gamari Date: Mon Jul 10 16:41:42 2017 -0400 Clean up release notes >--------------------------------------------------------------- b6146d284866d7d1b0a9370759054401c1303b1f docs/users_guide/8.2.1-notes.rst | 144 +++++++++++++++++---------------------- 1 file changed, 61 insertions(+), 83 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 b6146d284866d7d1b0a9370759054401c1303b1f From git at git.haskell.org Wed Jul 19 23:24:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:24:04 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Improve Wmissing-home-modules warning under Cabal (17bce7b) Message-ID: <20170719232404.716413A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/17bce7bccbc65058dc064acf1ef38a5466491c76/ghc >--------------------------------------------------------------- commit 17bce7bccbc65058dc064acf1ef38a5466491c76 Author: Ben Gamari Date: Tue Jul 11 11:54:59 2017 -0400 Improve Wmissing-home-modules warning under Cabal Reviewers: hvr, alanz, austin Reviewed By: alanz Subscribers: rwbarton, thomie GHC Trac Issues: #13899 Differential Revision: https://phabricator.haskell.org/D3686 (cherry picked from commit b0c9f34aa3da914524ef37294bba78afefc3ada7) >--------------------------------------------------------------- 17bce7bccbc65058dc064acf1ef38a5466491c76 compiler/main/GhcMake.hs | 7 ++++++- testsuite/tests/warnings/should_compile/MissingMod.stderr | 2 +- testsuite/tests/warnings/should_compile/T13727/T13727a.stderr | 2 +- testsuite/tests/warnings/should_compile/T13727/T13727b.stderr | 2 +- testsuite/tests/warnings/should_compile/T13727/T13727f.stderr | 3 ++- testsuite/tests/warnings/should_compile/T13727/T13727g.stderr | 3 ++- testsuite/tests/warnings/should_compile/T13727/T13727h.stderr | 2 +- testsuite/tests/warnings/should_compile/T13727/T13727i.stderr | 2 +- testsuite/tests/warnings/should_compile/T13727/T13727j.stderr | 2 +- 9 files changed, 16 insertions(+), 9 deletions(-) diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs index 57a9138..1d9e9e2 100644 --- a/compiler/main/GhcMake.hs +++ b/compiler/main/GhcMake.hs @@ -187,7 +187,12 @@ warnMissingHomeModules hsc_env mod_graph = missing = map (moduleName . ms_mod) $ filter (not . is_known_module) mod_graph - msg = text "Modules are not listed in command line: " + msg + | gopt Opt_BuildingCabalPackage dflags + = text "These modules are needed for compilation but not listed in your .cabal file's other-modules: " + <> sep (map ppr missing) + | otherwise + = text "Modules are not listed in command line but needed for compilation: " <> sep (map ppr missing) warn = makeIntoWarning (Reason Opt_WarnMissingHomeModules) diff --git a/testsuite/tests/warnings/should_compile/MissingMod.stderr b/testsuite/tests/warnings/should_compile/MissingMod.stderr index 0045092..119e72c 100644 --- a/testsuite/tests/warnings/should_compile/MissingMod.stderr +++ b/testsuite/tests/warnings/should_compile/MissingMod.stderr @@ -1,5 +1,5 @@ : warning: [-Wmissing-home-modules] - Modules are not listed in command line: MissingMod1 + Modules are not listed in command line but needed for compilation: MissingMod1 [1 of 2] Compiling MissingMod1 ( MissingMod1.hs, MissingMod1.o ) [2 of 2] Compiling MissingMod ( MissingMod.hs, MissingMod.o ) diff --git a/testsuite/tests/warnings/should_compile/T13727/T13727a.stderr b/testsuite/tests/warnings/should_compile/T13727/T13727a.stderr index 64ad6d2..c77fbc4 100644 --- a/testsuite/tests/warnings/should_compile/T13727/T13727a.stderr +++ b/testsuite/tests/warnings/should_compile/T13727/T13727a.stderr @@ -1,6 +1,6 @@ : warning: [-Wmissing-home-modules] - Modules are not listed in command line: M1 + Modules are not listed in command line but needed for compilation: M1 [1 of 2] Compiling M1 ( src-lib/M1.hs, src-lib/M1.o ) [2 of 2] Compiling Main ( src-exe/Main.hs, src-exe/Main.o ) Linking src-exe/Main ... diff --git a/testsuite/tests/warnings/should_compile/T13727/T13727b.stderr b/testsuite/tests/warnings/should_compile/T13727/T13727b.stderr index 64ad6d2..c77fbc4 100644 --- a/testsuite/tests/warnings/should_compile/T13727/T13727b.stderr +++ b/testsuite/tests/warnings/should_compile/T13727/T13727b.stderr @@ -1,6 +1,6 @@ : warning: [-Wmissing-home-modules] - Modules are not listed in command line: M1 + Modules are not listed in command line but needed for compilation: M1 [1 of 2] Compiling M1 ( src-lib/M1.hs, src-lib/M1.o ) [2 of 2] Compiling Main ( src-exe/Main.hs, src-exe/Main.o ) Linking src-exe/Main ... diff --git a/testsuite/tests/warnings/should_compile/T13727/T13727f.stderr b/testsuite/tests/warnings/should_compile/T13727/T13727f.stderr index 35bfae8..20a42ba 100644 --- a/testsuite/tests/warnings/should_compile/T13727/T13727f.stderr +++ b/testsuite/tests/warnings/should_compile/T13727/T13727f.stderr @@ -1,6 +1,7 @@ : warning: [-Wmissing-home-modules] - Modules are not listed in command line: M1 Main + Modules are not listed in command line but needed for compilation: M1 + Main [1 of 3] Compiling M1 ( src-lib/M1.hs, src-lib/M1.o ) [2 of 3] Compiling Main ( src-exe/Main.hs, src-exe/Main.o ) [3 of 3] Compiling AltMain ( src-exe/AltMain.hs, src-exe/AltMain.o ) diff --git a/testsuite/tests/warnings/should_compile/T13727/T13727g.stderr b/testsuite/tests/warnings/should_compile/T13727/T13727g.stderr index 35bfae8..20a42ba 100644 --- a/testsuite/tests/warnings/should_compile/T13727/T13727g.stderr +++ b/testsuite/tests/warnings/should_compile/T13727/T13727g.stderr @@ -1,6 +1,7 @@ : warning: [-Wmissing-home-modules] - Modules are not listed in command line: M1 Main + Modules are not listed in command line but needed for compilation: M1 + Main [1 of 3] Compiling M1 ( src-lib/M1.hs, src-lib/M1.o ) [2 of 3] Compiling Main ( src-exe/Main.hs, src-exe/Main.o ) [3 of 3] Compiling AltMain ( src-exe/AltMain.hs, src-exe/AltMain.o ) diff --git a/testsuite/tests/warnings/should_compile/T13727/T13727h.stderr b/testsuite/tests/warnings/should_compile/T13727/T13727h.stderr index 1832b38..a29f764 100644 --- a/testsuite/tests/warnings/should_compile/T13727/T13727h.stderr +++ b/testsuite/tests/warnings/should_compile/T13727/T13727h.stderr @@ -1,6 +1,6 @@ : warning: [-Wmissing-home-modules] - Modules are not listed in command line: M1 + Modules are not listed in command line but needed for compilation: M1 [1 of 3] Compiling M1 ( src-lib/M1.hs, src-lib/M1.o ) [2 of 3] Compiling Main ( src-exe/Main.hs, src-exe/Main.o ) [3 of 3] Compiling AltMain ( src-exe/AltMain.hs, src-exe/AltMain.o ) diff --git a/testsuite/tests/warnings/should_compile/T13727/T13727i.stderr b/testsuite/tests/warnings/should_compile/T13727/T13727i.stderr index 1832b38..a29f764 100644 --- a/testsuite/tests/warnings/should_compile/T13727/T13727i.stderr +++ b/testsuite/tests/warnings/should_compile/T13727/T13727i.stderr @@ -1,6 +1,6 @@ : warning: [-Wmissing-home-modules] - Modules are not listed in command line: M1 + Modules are not listed in command line but needed for compilation: M1 [1 of 3] Compiling M1 ( src-lib/M1.hs, src-lib/M1.o ) [2 of 3] Compiling Main ( src-exe/Main.hs, src-exe/Main.o ) [3 of 3] Compiling AltMain ( src-exe/AltMain.hs, src-exe/AltMain.o ) diff --git a/testsuite/tests/warnings/should_compile/T13727/T13727j.stderr b/testsuite/tests/warnings/should_compile/T13727/T13727j.stderr index f6d3197..e85f778 100644 --- a/testsuite/tests/warnings/should_compile/T13727/T13727j.stderr +++ b/testsuite/tests/warnings/should_compile/T13727/T13727j.stderr @@ -1,6 +1,6 @@ : warning: [-Wmissing-home-modules] - Modules are not listed in command line: Main + Modules are not listed in command line but needed for compilation: Main [1 of 3] Compiling M1 ( src-lib/M1.hs, src-lib/M1.o ) [2 of 3] Compiling Main ( src-exe/Main.hs, src-exe/Main.o ) [3 of 3] Compiling AltMain ( src-exe/AltMain.hs, src-exe/AltMain.o ) From git at git.haskell.org Wed Jul 19 23:24:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:24:10 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: configure: Ensure that we don't set LD to unusable linker (c23a84d) Message-ID: <20170719232410.00B933A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/c23a84d58e348d51632dfcafff81a2c94abcab0b/ghc >--------------------------------------------------------------- commit c23a84d58e348d51632dfcafff81a2c94abcab0b Author: Ben Gamari Date: Tue Jul 11 14:42:04 2017 -0400 configure: Ensure that we don't set LD to unusable linker Previously if we found an unusable linker in PATH (e.g. ld.lld on OS X) we would notice the -fuse-ld=... was broken, but neglected to reset LD to a usable linker. This resulted in brokenness on OS X when lld is in PATH. Test Plan: Validate on OS X with lld in PATH Reviewers: austin, hvr, angerman Reviewed By: angerman Subscribers: rwbarton, thomie, erikd, angerman GHC Trac Issues: #13541 Differential Revision: https://phabricator.haskell.org/D3713 (cherry picked from commit fcd2db14368fc6e0d35b13535a9663cfab7080a7) >--------------------------------------------------------------- c23a84d58e348d51632dfcafff81a2c94abcab0b aclocal.m4 | 12 +++++++----- 1 file changed, 7 insertions(+), 5 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 4ecd1bb..a561a41 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2338,18 +2338,20 @@ AC_DEFUN([FIND_LD],[ [enable_ld_override=yes]) if test "x$enable_ld_override" = "xyes"; then - AC_CHECK_TARGET_TOOLS([LD], [ld.gold ld.lld ld]) - UseLd='' + AC_CHECK_TARGET_TOOLS([TmpLd], [ld.gold ld.lld ld]) - out=`$LD --version` + out=`$TmpLd --version` case $out in "GNU ld"*) FP_CC_LINKER_FLAG_TRY(bfd, $2) ;; "GNU gold"*) FP_CC_LINKER_FLAG_TRY(gold, $2) ;; "LLD"*) FP_CC_LINKER_FLAG_TRY(lld, $2) ;; *) AC_MSG_NOTICE([unknown linker version $out]) ;; esac - if test "z$2" = "z"; then - AC_MSG_NOTICE([unable to convince '$CC' to use linker '$LD']) + if test "z$$2" = "z"; then + AC_MSG_NOTICE([unable to convince '$CC' to use linker '$TmpLd']) + AC_CHECK_TARGET_TOOL([LD], [ld]) + else + LD="$TmpLd" fi else AC_CHECK_TARGET_TOOL([LD], [ld]) From git at git.haskell.org Wed Jul 19 23:24:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:24:12 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Typeable: Always use UTF-8 string unpacking primitive (0ee8420) Message-ID: <20170719232412.B89D53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/0ee84202d6d051538582692e686a6b2a5a1b450f/ghc >--------------------------------------------------------------- commit 0ee84202d6d051538582692e686a6b2a5a1b450f Author: Ben Gamari Date: Tue Jul 18 17:50:07 2017 -0400 Typeable: Always use UTF-8 string unpacking primitive Reviewers: austin, hvr Subscribers: Phyx, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3734 (cherry picked from commit 6ab3c5fdd7d292deb65a3174eb298aa4b2348e32) >--------------------------------------------------------------- 0ee84202d6d051538582692e686a6b2a5a1b450f libraries/base/Data/Typeable/Internal.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index cf645ad..cf3ea07 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -117,7 +117,7 @@ tyConName :: TyCon -> String tyConName (TyCon _ _ _ n _ _) = trNameString n trNameString :: TrName -> String -trNameString (TrNameS s) = unpackCString# s +trNameString (TrNameS s) = unpackCStringUtf8# s trNameString (TrNameD s) = s tyConFingerprint :: TyCon -> Fingerprint @@ -361,7 +361,7 @@ instantiateKindRep vars = go = SomeTypeRep $ Fun (unsafeCoerceRep $ go a) (unsafeCoerceRep $ go b) go (KindRepTYPE r) = unkindedTypeRep $ tYPE `kApp` runtimeRepTypeRep r go (KindRepTypeLitS sort s) - = mkTypeLitFromString sort (unpackCString# s) + = mkTypeLitFromString sort (unpackCStringUtf8# s) go (KindRepTypeLitD sort s) = mkTypeLitFromString sort s @@ -569,7 +569,7 @@ pattern KindRepTypeLit sort t <- (getKindRepTypeLit -> Just (sort, t)) KindRepTYPE, KindRepTypeLit #-} getKindRepTypeLit :: KindRep -> Maybe (TypeLitSort, String) -getKindRepTypeLit (KindRepTypeLitS sort t) = Just (sort, unpackCString# t) +getKindRepTypeLit (KindRepTypeLitS sort t) = Just (sort, unpackCStringUtf8# t) getKindRepTypeLit (KindRepTypeLitD sort t) = Just (sort, t) getKindRepTypeLit _ = Nothing @@ -586,9 +586,9 @@ mkTyCon# pkg modl name n_kinds kind_rep where mod = Module (TrNameS pkg) (TrNameS modl) fingerprint :: Fingerprint - fingerprint = mkTyConFingerprint (unpackCString# pkg) - (unpackCString# modl) - (unpackCString# name) + fingerprint = mkTyConFingerprint (unpackCStringUtf8# pkg) + (unpackCStringUtf8# modl) + (unpackCStringUtf8# name) -- it is extremely important that this fingerprint computation -- remains in sync with that in TcTypeable to ensure that type From git at git.haskell.org Wed Jul 19 23:24:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:24:15 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: configure: Cleanup ARM COPY bug test artifacts (b847efb) Message-ID: <20170719232415.7A4D03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/b847efbcefc01b05e9ca3bdb39c868decde872d6/ghc >--------------------------------------------------------------- commit b847efbcefc01b05e9ca3bdb39c868decde872d6 Author: Ben Gamari Date: Fri Jul 7 23:16:47 2017 -0400 configure: Cleanup ARM COPY bug test artifacts (cherry picked from commit d7b17517e26007f537feab490509c0e13e0e239a) >--------------------------------------------------------------- b847efbcefc01b05e9ca3bdb39c868decde872d6 aclocal.m4 | 2 ++ 1 file changed, 2 insertions(+) diff --git a/aclocal.m4 b/aclocal.m4 index a561a41..79067eb 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2117,6 +2117,8 @@ EOF else AC_MSG_RESULT([unaffected]) fi + + rm -f aclib.s aclib.o aclib.so actest.s actest.o actest ;; *) ;; From git at git.haskell.org Wed Jul 19 23:24:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:24:18 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump terminfo submodule (b1c69dd) Message-ID: <20170719232418.3DC3E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/b1c69dd2ab39c984a71fe8f380f6b2b5fb59ea8b/ghc >--------------------------------------------------------------- commit b1c69dd2ab39c984a71fe8f380f6b2b5fb59ea8b Author: Ben Gamari Date: Wed Jul 19 17:47:34 2017 -0400 Bump terminfo submodule It seems that the 0.4.1.0 tag mysteriously moved. Thankfully there is only one small commit difference. >--------------------------------------------------------------- b1c69dd2ab39c984a71fe8f380f6b2b5fb59ea8b libraries/terminfo | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/terminfo b/libraries/terminfo index c39f12c..02ebf00 160000 --- a/libraries/terminfo +++ b/libraries/terminfo @@ -1 +1 @@ -Subproject commit c39f12cf41fc47b54723d9e9a08487e8e9dd119e +Subproject commit 02ebf00cb2ab59d7924909306b7a791c7959f703 From git at git.haskell.org Wed Jul 19 23:24:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:24:20 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump deepseq submodule to 1.4.3 (1817fe1) Message-ID: <20170719232420.E7F433A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/1817fe1ed73f01ac99399c742878ac7a805ce8c7/ghc >--------------------------------------------------------------- commit 1817fe1ed73f01ac99399c742878ac7a805ce8c7 Author: Ben Gamari Date: Wed Jul 19 17:53:32 2017 -0400 Bump deepseq submodule to 1.4.3 >--------------------------------------------------------------- 1817fe1ed73f01ac99399c742878ac7a805ce8c7 libraries/deepseq | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/deepseq b/libraries/deepseq index 65dd864..0b22c98 160000 --- a/libraries/deepseq +++ b/libraries/deepseq @@ -1 +1 @@ -Subproject commit 65dd864d0d2f5cf415064fc214261b9270a924cf +Subproject commit 0b22c9825ef79c1ee41d2f19e7c997f5cdc93494 From git at git.haskell.org Wed Jul 19 23:24:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:24:23 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump xhtml submodule to 3000.2.2 (bac7043) Message-ID: <20170719232423.A8AC23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/bac70437614ad4eaf7128996724e3a230a32c38f/ghc >--------------------------------------------------------------- commit bac70437614ad4eaf7128996724e3a230a32c38f Author: Ben Gamari Date: Wed Jul 19 18:07:17 2017 -0400 Bump xhtml submodule to 3000.2.2 >--------------------------------------------------------------- bac70437614ad4eaf7128996724e3a230a32c38f libraries/xhtml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/xhtml b/libraries/xhtml index 8a8c8a4..6358594 160000 --- a/libraries/xhtml +++ b/libraries/xhtml @@ -1 +1 @@ -Subproject commit 8a8c8a48bac2d3ed306b610a2e9fa393b5a7ffa5 +Subproject commit 6358594eb5139f6760e2ada72718d69fed5a1015 From git at git.haskell.org Wed Jul 19 23:24:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:24:26 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump Win32 submodule to 2.5.4.1 (aca1916) Message-ID: <20170719232426.69BFE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/aca1916d0060ff9e23ac004f6459859d68af6c36/ghc >--------------------------------------------------------------- commit aca1916d0060ff9e23ac004f6459859d68af6c36 Author: Ben Gamari Date: Wed Jul 19 18:11:40 2017 -0400 Bump Win32 submodule to 2.5.4.1 >--------------------------------------------------------------- aca1916d0060ff9e23ac004f6459859d68af6c36 libraries/Win32 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Win32 b/libraries/Win32 index b5ebb64..147a0af 160000 --- a/libraries/Win32 +++ b/libraries/Win32 @@ -1 +1 @@ -Subproject commit b5ebb64894cf166f9ee84ee91802486c76e480cf +Subproject commit 147a0af92ac74ec58b209e16aeb1cf03bddf9482 From git at git.haskell.org Wed Jul 19 23:24:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:24:29 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump unix submodule to 2.7.2.2 (889b22e) Message-ID: <20170719232429.20AD73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/889b22ef8905fb4c83f63ae1c617cb977eeddc44/ghc >--------------------------------------------------------------- commit 889b22ef8905fb4c83f63ae1c617cb977eeddc44 Author: Ben Gamari Date: Wed Jul 19 18:32:56 2017 -0400 Bump unix submodule to 2.7.2.2 >--------------------------------------------------------------- 889b22ef8905fb4c83f63ae1c617cb977eeddc44 libraries/unix | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/unix b/libraries/unix index eb5fc94..fcaa530 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit eb5fc942f8f570e754bba0f57a8fdaec3400194f +Subproject commit fcaa530a8fdd3897353bdf246752a91d675aad46 From git at git.haskell.org Wed Jul 19 23:26:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:26:45 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Can now load up git note data into the python test driver. Working on issue #12758. (e44d040) Message-ID: <20170719232645.BE05B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/e44d040c7aaf53838fb377b928b2c5b1889ee17e/ghc >--------------------------------------------------------------- commit e44d040c7aaf53838fb377b928b2c5b1889ee17e Author: Jared Weakly Date: Tue Jul 18 12:17:57 2017 -0700 Can now load up git note data into the python test driver. Working on issue #12758. Reviewers: austin, bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3758 >--------------------------------------------------------------- e44d040c7aaf53838fb377b928b2c5b1889ee17e testsuite/driver/runtests.py | 6 ++++-- testsuite/driver/testutil.py | 12 +++++++++--- 2 files changed, 13 insertions(+), 5 deletions(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index 996dae1..239003c 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -337,8 +337,10 @@ else: sys.stdout.flush() summary(t, sys.stdout, config.no_print_summary) - print("Only perf tests: " + str(config.only_perf_tests) + "\n") - print("Skip perf tests: " + str(config.skip_perf_tests) + "\n") + + if config.use_git_notes: + note = subprocess.check_output(["git","notes","--ref=perf","append","-m", "\n".join(config.accumulate_metrics)]) + parse_git_notes('perf') # Should this be hardcoded? Most likely not... if config.summary_file != '': with open(config.summary_file, 'w') as file: diff --git a/testsuite/driver/testutil.py b/testsuite/driver/testutil.py index 084ef7e..6eb7aaa 100644 --- a/testsuite/driver/testutil.py +++ b/testsuite/driver/testutil.py @@ -47,9 +47,15 @@ def lndir(srcdir, dstdir): os.mkdir(dst) lndir(src, dst) -# def git_append(note): -# def print_metrics(): -# print(config.accumulate_metrics) +# This function allows one to read in git notes from the commandline +# and then breaks it into a list of dictionaries that can be parsed +# later on in the testing functions. +def parse_git_notes(namespace): + logFields = ['TEST_ENV','TEST','WAY','METRIC','VALUE'] + log = subprocess.check_output(['git', 'notes', '--ref=' + namespace, 'show']).decode('utf-8') + log = log.strip('\n').split('\n') + log = [entry.strip('\t').split('\t') for entry in log] + log = [dict(zip(logFields, row)) for row in log] # On Windows, os.symlink is not defined with Python 2.7, but is in Python 3 # when using msys2, as GHC does. Unfortunately, only Administrative users have From git at git.haskell.org Wed Jul 19 23:26:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:26:51 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Fixing random diverging that happened somehow (cd4e438) Message-ID: <20170719232651.40F4B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/cd4e4382e4931fe5509ac6ca50211a218085e845/ghc >--------------------------------------------------------------- commit cd4e4382e4931fe5509ac6ca50211a218085e845 Merge: becf05e 92e5349 Author: Jared Weakly Date: Wed Jul 19 16:28:11 2017 -0700 Fixing random diverging that happened somehow >--------------------------------------------------------------- cd4e4382e4931fe5509ac6ca50211a218085e845 From git at git.haskell.org Wed Jul 19 23:26:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:26:48 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Small changes to address Ben's comments (becf05e) Message-ID: <20170719232648.7681B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/becf05e33bed53bf3940d7d418237fcceba696c4/ghc >--------------------------------------------------------------- commit becf05e33bed53bf3940d7d418237fcceba696c4 Author: Jared Weakly Date: Tue Jul 18 17:35:34 2017 -0700 Small changes to address Ben's comments Signed-off-by: Jared Weakly >--------------------------------------------------------------- becf05e33bed53bf3940d7d418237fcceba696c4 testsuite/driver/runtests.py | 13 +++++++++---- testsuite/driver/testglobals.py | 2 +- testsuite/driver/testlib.py | 5 ++--- testsuite/driver/testutil.py | 6 ++++-- 4 files changed, 16 insertions(+), 10 deletions(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index 239003c..e0c652a 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -54,9 +54,9 @@ long_options = [ "check-files-written", # check files aren't written by multiple tests "verbose=", # verbose (0,1,2 so far) "skip-perf-tests", # skip performance tests - "only-perf-tests", # Only do performance tests + "only-perf-tests", # Only do performance tests "use-git-notes", # use git notes to store metrics. NOTE: This is expected to become the default and will eventually be taken out. - "TEST_ENV=", # Override default chosen test-env. + "test-env=", # Override default chosen test-env. ] opts, args = getopt.getopt(sys.argv[1:], "e:", long_options) @@ -125,8 +125,8 @@ for opt,arg in opts: sys.exit(1) config.verbose = int(arg) - if opt == '--TEST_ENV': - config.TEST_ENV = arg + if opt == '--test-env': + config.test_env = arg config.cygwin = False @@ -338,6 +338,11 @@ else: summary(t, sys.stdout, config.no_print_summary) + # This here is loading up all of the git notes into memory. + # It's most likely in the wrong spot and I haven't fully fleshed out + # where exactly I'm putting this and how I'm refactoring the performance + # test running logic. + # Currently this is useful for debugging, at least. if config.use_git_notes: note = subprocess.check_output(["git","notes","--ref=perf","append","-m", "\n".join(config.accumulate_metrics)]) parse_git_notes('perf') # Should this be hardcoded? Most likely not... diff --git a/testsuite/driver/testglobals.py b/testsuite/driver/testglobals.py index bd8eefe..aa81b32 100644 --- a/testsuite/driver/testglobals.py +++ b/testsuite/driver/testglobals.py @@ -125,7 +125,7 @@ class TestConfig: # To accumulate the metrics for the git notes self.accumulate_metrics = [] # Has the user defined a custom test environment? Local is default. - self.TEST_ENV = 'local' + self.test_env = 'local' global config config = TestConfig() diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 8657a12..58e0c6e 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1085,7 +1085,6 @@ def stats( name, way, stats_file ): # Check -t stats info def checkStats(name, way, stats_file, range_fields): - full_name = name + '(' + way + ')' result = passed() @@ -1111,8 +1110,8 @@ def checkStats(name, way, stats_file, range_fields): # Add val into the git note if option is set. if config.use_git_notes: - test_env = config.TEST_ENV - config.accumulate_metrics.append(test_env + '\t' + name + '\t' + way + '\t' + field + '\t' + str(val)) + test_env = config.test_env + config.accumulate_metrics.append('\t'.join([test_env, name, way, field, str(val)])) if val < lowerBound: print(field, 'value is too low:') diff --git a/testsuite/driver/testutil.py b/testsuite/driver/testutil.py index 6eb7aaa..6939b8a 100644 --- a/testsuite/driver/testutil.py +++ b/testsuite/driver/testutil.py @@ -54,8 +54,10 @@ def parse_git_notes(namespace): logFields = ['TEST_ENV','TEST','WAY','METRIC','VALUE'] log = subprocess.check_output(['git', 'notes', '--ref=' + namespace, 'show']).decode('utf-8') log = log.strip('\n').split('\n') - log = [entry.strip('\t').split('\t') for entry in log] - log = [dict(zip(logFields, row)) for row in log] + log = [line.strip('\t').split('\t') for line in log] + log = [dict(zip(logFields, field)) for field in log] + return log + # Add a print statement here if you want to see what's being loaded from git notes. # On Windows, os.symlink is not defined with Python 2.7, but is in Python 3 # when using msys2, as GHC does. Unfortunately, only Administrative users have From git at git.haskell.org Wed Jul 19 23:29:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:29:19 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Ensure that hs_try_putmvar003 terminates (a051b55) Message-ID: <20170719232919.99F043A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a051b555e32d7d8a08472e36be4cb08716d6d8ad/ghc >--------------------------------------------------------------- commit a051b555e32d7d8a08472e36be4cb08716d6d8ad Author: Ben Gamari Date: Wed Jul 19 15:06:02 2017 -0400 testsuite: Ensure that hs_try_putmvar003 terminates Test Plan: Validate Reviewers: austin, simonmar Reviewed By: simonmar Subscribers: simonmar, rwbarton, thomie GHC Trac Issues: #13434 Differential Revision: https://phabricator.haskell.org/D3724 >--------------------------------------------------------------- a051b555e32d7d8a08472e36be4cb08716d6d8ad testsuite/tests/concurrent/should_run/hs_try_putmvar003.hs | 4 ++-- testsuite/tests/concurrent/should_run/hs_try_putmvar003_c.c | 10 +++++++--- 2 files changed, 9 insertions(+), 5 deletions(-) diff --git a/testsuite/tests/concurrent/should_run/hs_try_putmvar003.hs b/testsuite/tests/concurrent/should_run/hs_try_putmvar003.hs index 4442698..d0c9739 100644 --- a/testsuite/tests/concurrent/should_run/hs_try_putmvar003.hs +++ b/testsuite/tests/concurrent/should_run/hs_try_putmvar003.hs @@ -51,7 +51,7 @@ makeExternalCall q = mask_ $ do data CallbackQueue foreign import ccall "mkCallbackQueue" - mkCallbackQueue :: Int -> IO (Ptr CallbackQueue) + mkCallbackQueue :: Int -> Int -> IO (Ptr CallbackQueue) foreign import ccall "destroyCallbackQueue" destroyCallbackQueue :: Ptr CallbackQueue -> IO () @@ -77,7 +77,7 @@ foreign export ccall callbackPutMVar :: StablePtr PrimMVar -> IO () experiment :: Bool -> Int -> Int -> Int -> IO () experiment use_foreign_export x y z = do mvars <- replicateM x $ async $ do - bracket (mkCallbackQueue (fromEnum use_foreign_export)) + bracket (mkCallbackQueue (fromEnum use_foreign_export) (z*y)) destroyCallbackQueue $ \q -> do mvars <- replicateM y $ async $ replicateM_ z $ void $ makeExternalCall q diff --git a/testsuite/tests/concurrent/should_run/hs_try_putmvar003_c.c b/testsuite/tests/concurrent/should_run/hs_try_putmvar003_c.c index aa65144..d67ca43 100644 --- a/testsuite/tests/concurrent/should_run/hs_try_putmvar003_c.c +++ b/testsuite/tests/concurrent/should_run/hs_try_putmvar003_c.c @@ -9,6 +9,9 @@ struct callback_queue { pthread_mutex_t lock; pthread_cond_t cond; int use_foreign_export; + // How many requests will be submitted to this queue? + // (e.g. n_threads * n_requests_per_thread) + int n_requests; struct callback *pending; }; @@ -24,7 +27,7 @@ void* callback(struct callback_queue *q) struct callback *cb; pthread_mutex_lock(&q->lock); - do { + for (int i=0; i < q->n_requests; i++) { if (q->pending == NULL) { pthread_cond_wait(&q->cond,&q->lock); } @@ -39,7 +42,7 @@ void* callback(struct callback_queue *q) } free(cb); } - } while (1); + } pthread_mutex_unlock(&q->lock); hs_thread_done(); @@ -48,7 +51,7 @@ void* callback(struct callback_queue *q) typedef void* threadfunc(void *); -struct callback_queue* mkCallbackQueue(int use_foreign_export) +struct callback_queue* mkCallbackQueue(int use_foreign_export, int n_requests) { struct callback_queue *q = malloc(sizeof(struct callback_queue)); pthread_t t; @@ -56,6 +59,7 @@ struct callback_queue* mkCallbackQueue(int use_foreign_export) pthread_cond_init(&q->cond, NULL); q->pending = NULL; q->use_foreign_export = use_foreign_export; + q->n_requests = n_requests; pthread_create(&t, NULL, (threadfunc*)callback, q); return q; } From git at git.haskell.org Wed Jul 19 23:29:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:29:22 +0000 (UTC) Subject: [commit: ghc] master: Allow visible type application for [] (c9e4c86) Message-ID: <20170719232922.B7F843A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c9e4c861c6855e03bd14b182d2173da559e98d85/ghc >--------------------------------------------------------------- commit c9e4c861c6855e03bd14b182d2173da559e98d85 Author: Ryan Scott Date: Wed Jul 19 15:06:12 2017 -0400 Allow visible type application for [] This amounts to a one-line change in `tcExpr`. I've added a Note to explain what is going on. This requires a separate change in the pattern-match checker to account for the fact that typechecked `[]` expressions become `ConLikeOut`s, not `ExplicitList`s. Test Plan: make test TEST=T13680 Reviewers: goldfire, mpickering, austin, bgamari Reviewed By: mpickering, bgamari Subscribers: rwbarton, thomie, goldfire GHC Trac Issues: #13680 Differential Revision: https://phabricator.haskell.org/D3733 >--------------------------------------------------------------- c9e4c861c6855e03bd14b182d2173da559e98d85 compiler/typecheck/TcExpr.hs | 31 ++++++++++++++++++++++ testsuite/tests/typecheck/should_compile/T13680.hs | 5 ++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 37 insertions(+) diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs index cf8bf0c..0e1e866 100644 --- a/compiler/typecheck/TcExpr.hs +++ b/compiler/typecheck/TcExpr.hs @@ -54,6 +54,7 @@ import NameEnv import NameSet import RdrName import TyCon +import TyCoRep import Type import TcEvidence import VarSet @@ -1170,6 +1171,16 @@ tcApp m_herald orig_fun orig_args res_ty ; sel_name <- disambiguateSelector lbl sig_tc_ty ; go (L loc (HsRecFld (Unambiguous lbl sel_name))) args } + -- See Note [Visible type application for the empty list constructor] + go (L loc (ExplicitList _ Nothing [])) [Right ty_arg] + = do { ty_arg' <- tcHsTypeApp ty_arg liftedTypeKind + ; let list_ty = TyConApp listTyCon [ty_arg'] + ; _ <- tcSubTypeDS (OccurrenceOf nilDataConName) GenSigCtxt + list_ty res_ty + ; let expr :: LHsExpr GhcTcId + expr = L loc $ ExplicitList ty_arg' Nothing [] + ; return (idHsWrapper, expr, []) } + go fun args = do { -- Type-check the function ; (fun1, fun_sigma) <- tcInferFun fun @@ -1198,6 +1209,26 @@ mk_app_msg fun = sep [ text "The function" <+> quotes (ppr fun) mk_op_msg :: LHsExpr GhcRn -> SDoc mk_op_msg op = text "The operator" <+> quotes (ppr op) <+> text "takes" +{- +Note [Visible type application for the empty list constructor] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Getting the expression [] @Int to typecheck is slightly tricky since [] isn't +an ordinary data constructor. By default, when tcExpr typechecks a list +expression, it wraps the expression in a coercion, which gives it a type to the +effect of p[a]. It isn't until later zonking that the type becomes +forall a. [a], but that's too late for visible type application. + +The workaround is to check for empty list expressions that have a visible type +argument in tcApp, and if so, directly typecheck [] @ty data constructor name. +This avoids the intermediate coercion and produces an expression of type [ty], +as one would intuitively expect. + +Unfortunately, this workaround isn't terribly robust, since more involved +expressions such as (let in []) @Int won't work. Until a more elegant fix comes +along, however, this at least allows direct type application on [] to work, +which is better than before. +-} + ---------------- tcInferFun :: LHsExpr GhcRn -> TcM (LHsExpr GhcTcId, TcSigmaType) -- Infer type of a function diff --git a/testsuite/tests/typecheck/should_compile/T13680.hs b/testsuite/tests/typecheck/should_compile/T13680.hs new file mode 100644 index 0000000..7c1a855 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13680.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE TypeApplications #-} +module T13680 where + +foo :: [Int] +foo = [] @Int diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index d6aaef5..8f7996c 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -561,6 +561,7 @@ 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, ['']) +test('T13680', normal, compile, ['']) test('T13785', normal, compile, ['']) test('T13804', normal, compile, ['']) test('T13822', normal, compile, ['']) From git at git.haskell.org Wed Jul 19 23:29:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:29:25 +0000 (UTC) Subject: [commit: ghc] master: Fix links to SPJ’s papers (fixes #12578) (1ed41a7) Message-ID: <20170719232925.7C9983A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1ed41a7413a45e11a9bad3aafcfb7ee3f26236e4/ghc >--------------------------------------------------------------- commit 1ed41a7413a45e11a9bad3aafcfb7ee3f26236e4 Author: Takenobu Tani Date: Wed Jul 19 15:06:27 2017 -0400 Fix links to SPJ’s papers (fixes #12578) This fixes #12578. Update links to SPJ's papers in following files: * compiler/coreSyn/CoreSyn.hs * docs/users_guide/using-optimisation.rst * docs/users_guide/parallel.rst * docs/users_guide/glasgow_exts.rst This commit is for ghc-8.2 branch. Test Plan: build Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #12578 Differential Revision: https://phabricator.haskell.org/D3745 >--------------------------------------------------------------- 1ed41a7413a45e11a9bad3aafcfb7ee3f26236e4 compiler/coreSyn/CoreSyn.hs | 2 +- docs/users_guide/glasgow_exts.rst | 8 ++++---- docs/users_guide/parallel.rst | 4 ++-- docs/users_guide/using-optimisation.rst | 2 +- 4 files changed, 8 insertions(+), 8 deletions(-) diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs index a669437..13cf8ae 100644 --- a/compiler/coreSyn/CoreSyn.hs +++ b/compiler/coreSyn/CoreSyn.hs @@ -137,7 +137,7 @@ These data types are the heart of the compiler -} -- | This is the data type that represents GHCs core intermediate language. Currently --- GHC uses System FC for this purpose, +-- GHC uses System FC for this purpose, -- which is closely related to the simpler and better known System F . -- -- We get from Haskell source to this Core language in a number of stages: diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index c3a2d69..0dbd03e 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -1150,7 +1150,7 @@ Generalised list comprehensions are a further enhancement to the list comprehension syntactic sugar to allow operations such as sorting and grouping which are familiar from SQL. They are fully described in the paper `Comprehensive comprehensions: comprehensions with "order by" and -"group by" `__, +"group by" `__, except that the syntax we use differs slightly from the paper. The extension is enabled with the flag :ghc-flag:`-XTransformListComp`. @@ -5839,7 +5839,7 @@ reduction step makes the problem smaller by at least one constructor. You can find lots of background material about the reason for these restrictions in the paper `Understanding functional dependencies via Constraint Handling -Rules `__. +Rules `__. For example, these are okay: @@ -9382,7 +9382,7 @@ restriction is not closed, and hence may in turn prevent generalisation of bindings that mention it. The rationale for this more conservative strategy is given in `the -papers `__ +papers `__ "Let should not be generalised" and "Modular type inference with local assumptions", and a related `blog post `__. @@ -10655,7 +10655,7 @@ ignore the problems in ``a``. For more motivation and details please refer to the :ghc-wiki:`Wiki ` page or the `original -paper `__. +paper `__. Enabling deferring of type errors --------------------------------- diff --git a/docs/users_guide/parallel.rst b/docs/users_guide/parallel.rst index 07dc60f..bac7754 100644 --- a/docs/users_guide/parallel.rst +++ b/docs/users_guide/parallel.rst @@ -47,14 +47,14 @@ The functions exported by this library include: - Synchronised mutable variables, called ``MVars`` - Support for bound threads; see the paper `Extending the FFI with - concurrency `__. + concurrency `__. Software Transactional Memory ----------------------------- GHC now supports a new way to coordinate the activities of Concurrent Haskell threads, called Software Transactional Memory (STM). The `STM -papers `__ +papers `__ are an excellent introduction to what STM is, and how to use it. The main library you need to use is the `stm diff --git a/docs/users_guide/using-optimisation.rst b/docs/users_guide/using-optimisation.rst index 88356df..185e590 100644 --- a/docs/users_guide/using-optimisation.rst +++ b/docs/users_guide/using-optimisation.rst @@ -230,7 +230,7 @@ by saying ``-fno-wombat``. Usually GHC black-holes a thunk only when it switches threads. This flag makes it do so as soon as the thunk is entered. See `Haskell on a shared-memory - multiprocessor `__. + multiprocessor `__. .. ghc-flag:: -fexcess-precision From git at git.haskell.org Wed Jul 19 23:29:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:29:29 +0000 (UTC) Subject: [commit: ghc] master: Fix #13983 by creating a TyConFlavour type, and using it (6e3c901) Message-ID: <20170719232929.69A243A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6e3c901db7a624d030614113c51be5731d1ac862/ghc >--------------------------------------------------------------- commit 6e3c901db7a624d030614113c51be5731d1ac862 Author: Ryan Scott Date: Wed Jul 19 15:07:01 2017 -0400 Fix #13983 by creating a TyConFlavour type, and using it An error message was referring to a type synonym as a datatype. Annoyingly, learning that the TyCon over which the error message is operating is actually a type synonym was previously impossible, since that code only had access to a TcTyCon, which doesn't retain any information about what sort of TyCon it is. To rectify this, I created a new TyConFlavour datatype, intended to capture roughly what sort of TyCon we're dealing with. I then performing the necessary plumbing to ensure all TcTyCons have a TyConFlavour, and propagated this information through to the relevant error message. Test Plan: ./validate Reviewers: goldfire, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #13983 Differential Revision: https://phabricator.haskell.org/D3747 >--------------------------------------------------------------- 6e3c901db7a624d030614113c51be5731d1ac862 compiler/typecheck/TcHsType.hs | 28 ++--- compiler/typecheck/TcPat.hs | 4 +- compiler/typecheck/TcTyClsDecls.hs | 41 ++++--- compiler/typecheck/TcValidity.hs | 8 +- compiler/types/TyCon.hs | 128 ++++++++++++++++----- testsuite/tests/ghci/scripts/T7873.stderr | 2 +- testsuite/tests/typecheck/should_fail/T13983.hs | 7 ++ .../tests/typecheck/should_fail/T13983.stderr | 8 ++ testsuite/tests/typecheck/should_fail/all.T | 1 + 9 files changed, 161 insertions(+), 66 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 6e3c901db7a624d030614113c51be5731d1ac862 From git at git.haskell.org Wed Jul 19 23:29:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:29:32 +0000 (UTC) Subject: [commit: ghc] master: Add Haddocks for Eq (STRef a) and Eq (IORef a) (0b89b2d) Message-ID: <20170719232932.3C5483A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0b89b2de8f67849a89e36bb4fcc03a47333627bf/ghc >--------------------------------------------------------------- commit 0b89b2de8f67849a89e36bb4fcc03a47333627bf Author: Adam Sandberg Eriksson Date: Wed Jul 19 15:07:44 2017 -0400 Add Haddocks for Eq (STRef a) and Eq (IORef a) Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: RyanGlScott, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3750 >--------------------------------------------------------------- 0b89b2de8f67849a89e36bb4fcc03a47333627bf libraries/base/GHC/IORef.hs | 9 ++++----- libraries/base/GHC/STRef.hs | 5 +++-- 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/libraries/base/GHC/IORef.hs b/libraries/base/GHC/IORef.hs index 0736567..0832be0 100644 --- a/libraries/base/GHC/IORef.hs +++ b/libraries/base/GHC/IORef.hs @@ -31,11 +31,10 @@ import GHC.IO -- |A mutable variable in the 'IO' monad newtype IORef a = IORef (STRef RealWorld a) - --- explicit instance because Haddock can't figure out a derived one --- | @since 4.1.0.0 -instance Eq (IORef a) where - IORef x == IORef y = x == y + deriving Eq + -- ^ Pointer equality. + -- + -- @since 4.1.0.0 -- |Build a new 'IORef' newIORef :: a -> IO (IORef a) diff --git a/libraries/base/GHC/STRef.hs b/libraries/base/GHC/STRef.hs index 22db7f3..a6e4292 100644 --- a/libraries/base/GHC/STRef.hs +++ b/libraries/base/GHC/STRef.hs @@ -44,7 +44,8 @@ writeSTRef (STRef var#) val = ST $ \s1# -> case writeMutVar# var# val s1# of { s2# -> (# s2#, () #) } --- Just pointer equality on mutable references: --- | @since 2.01 +-- | Pointer equality. +-- +-- @since 2.01 instance Eq (STRef s a) where STRef v1# == STRef v2# = isTrue# (sameMutVar# v1# v2#) From git at git.haskell.org Wed Jul 19 23:29:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:29:34 +0000 (UTC) Subject: [commit: ghc] master: dmdAnal: Ensure that ExnStr flag isn't dropped inappropriately (c940e3b) Message-ID: <20170719232934.F10A93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c940e3b92f4527ca59fcae93f36c869de3e7ccb9/ghc >--------------------------------------------------------------- commit c940e3b92f4527ca59fcae93f36c869de3e7ccb9 Author: Ben Gamari Date: Wed Jul 19 15:07:52 2017 -0400 dmdAnal: Ensure that ExnStr flag isn't dropped inappropriately This fixes #13977 and consequently #13615. Here an optimization in the demand analyser was too liberal, causing us to drop the ExnStr flag and consequently resulting in incorrect demand signatures. This manifested as a segmentation fault in #13615 as we incorrectly concluded that an application of catchRetry# would bottom. Specifically, we had orElse' :: STM a -> STM a -> STM a orElse' x = catchRetry# x y where y = {- some action -} Where the catchRetry# primop places a demand of on its first argument. However, due to #13977 the demand analyser would assign a demand of on the first argument of orElse'. Note the missing `x`. case orElse' bottomingAction anotherAction of { x -> Just x } being transformed to, case orElse' bottomingAction anotherAction of {} by the simplifier. This would naturally blow up when orElse' returned at runtime, causing the segmentation fault described in #13615. Test Plan: Validate, perhaps add a testcase Reviewers: austin, simonpj Reviewed By: simonpj Subscribers: rwbarton, thomie GHC Trac Issues: #13977, #13615 Differential Revision: https://phabricator.haskell.org/D3756 >--------------------------------------------------------------- c940e3b92f4527ca59fcae93f36c869de3e7ccb9 compiler/basicTypes/Demand.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index b6296f4..0262edc 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -1442,8 +1442,11 @@ postProcessDmdResult _ res = res postProcessDmdEnv :: DmdShell -> DmdEnv -> DmdEnv postProcessDmdEnv ds@(JD { sd = ss, ud = us }) env | Abs <- us = emptyDmdEnv - | Str _ _ <- ss - , Use One _ <- us = env -- Shell is a no-op + -- In this case (postProcessDmd ds) == id; avoid a redundant rebuild + -- of the environment. Be careful, bad things will happen if this doesn't + -- match postProcessDmd (see #13977). + | Str VanStr _ <- ss + , Use One _ <- us = env | otherwise = mapVarEnv (postProcessDmd ds) env -- For the Absent case just discard all usage information -- We only processed the thing at all to analyse the body From git at git.haskell.org Wed Jul 19 23:31:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:31:44 +0000 (UTC) Subject: [commit: ghc] master: typo: -XUndeci[d]ableInstances (927e781) Message-ID: <20170719233144.270063A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/927e7810f7dcea295c1f8e93535835e52da0edbb/ghc >--------------------------------------------------------------- commit 927e7810f7dcea295c1f8e93535835e52da0edbb Author: Chris Martin Date: Sat Jul 15 19:23:50 2017 -0500 typo: -XUndeci[d]ableInstances >--------------------------------------------------------------- 927e7810f7dcea295c1f8e93535835e52da0edbb 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 0dbd03e..418e7cb 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -7118,7 +7118,7 @@ However see :ref:`ghci-decls` for the overlap rules in GHCi. Decidability of type synonym instances ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -.. ghc-flag:: -XUndeciableInstances +.. ghc-flag:: -XUndecidableInstances Relax restrictions on the decidability of type synonym family instances. From git at git.haskell.org Wed Jul 19 23:31:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Jul 2017 23:31:46 +0000 (UTC) Subject: [commit: ghc] master: base: Improve docs to clarify when finalizers may not be run (b066d93) Message-ID: <20170719233146.D35E03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b066d936a919f6943de1acdc358d9e014b2cc663/ghc >--------------------------------------------------------------- commit b066d936a919f6943de1acdc358d9e014b2cc663 Author: Andrew Martin Date: Thu Jul 13 11:09:34 2017 -0400 base: Improve docs to clarify when finalizers may not be run >--------------------------------------------------------------- b066d936a919f6943de1acdc358d9e014b2cc663 libraries/base/System/Mem/Weak.hs | 26 ++++++++++++++++++++++++++ 1 file changed, 26 insertions(+) diff --git a/libraries/base/System/Mem/Weak.hs b/libraries/base/System/Mem/Weak.hs index b9580b5..3a00696 100644 --- a/libraries/base/System/Mem/Weak.hs +++ b/libraries/base/System/Mem/Weak.hs @@ -67,6 +67,10 @@ module System.Mem.Weak ( -- * A precise semantics -- $precise + + -- * Implementation notes + + -- $notes ) where import GHC.Weak @@ -140,3 +144,25 @@ A heap object is /reachable/ if: * It is the value or finalizer of a weak pointer object whose key is reachable. -} +{- $notes + +A finalizer is not always called after its weak pointer\'s object becomes +unreachable. There are two situations that can cause this: + + * If the object becomes unreachable right before the program exits, + then GC may not be performed. Finalizers run during GC, so finalizers + associated with the object do not run if GC does not happen. + + * If a finalizer throws an exception, subsequent finalizers that had + been queued to run after it do not get run. This behavior may change + in a future release. See issue + on the issue tracker. Writing a finalizer that throws exceptions is + discouraged. + +Other than these two caveats, users can always expect that a finalizer +will be run after its weak pointer\'s object becomes unreachable. However, +the second caveat means that users need to trust that all of their +transitive dependencies do not throw exceptions in finalizers, since +any finalizers can end up queued together. + +-} From git at git.haskell.org Thu Jul 20 02:18:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 02:18:00 +0000 (UTC) Subject: [commit: ghc] master: Typeable: Ensure that promoted data family instance tycons get bindings (cc839c5) Message-ID: <20170720021800.E53E93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cc839c57ff9c80b50d39e8e2e66a18674bab3486/ghc >--------------------------------------------------------------- commit cc839c57ff9c80b50d39e8e2e66a18674bab3486 Author: Ben Gamari Date: Wed Jul 19 19:33:00 2017 -0400 Typeable: Ensure that promoted data family instance tycons get bindings This fixes #13915, where the promoted tycons belonging to data family instances wouldn't get Typeable bindings, resulting in missing declarations. Test Plan: Validate with included testcases Reviewers: austin, simonpj Reviewed By: simonpj Subscribers: simonpj, RyanGlScott, rwbarton, thomie GHC Trac Issues: #13915 Differential Revision: https://phabricator.haskell.org/D3759 >--------------------------------------------------------------- cc839c57ff9c80b50d39e8e2e66a18674bab3486 compiler/typecheck/TcEnv.hs | 11 +++++++---- compiler/typecheck/TcRnTypes.hs | 3 ++- compiler/typecheck/TcTypeable.hs | 8 ++++---- testsuite/tests/perf/compiler/all.T | 3 ++- testsuite/tests/typecheck/should_compile/T13915a.hs | 7 +++++++ .../T11164b.hs => typecheck/should_compile/T13915a_Foo.hs} | 5 ++--- testsuite/tests/typecheck/should_compile/T13915b.hs | 11 +++++++++++ testsuite/tests/typecheck/should_compile/all.T | 2 ++ 8 files changed, 37 insertions(+), 13 deletions(-) diff --git a/compiler/typecheck/TcEnv.hs b/compiler/typecheck/TcEnv.hs index 935ad3d..12f8a1d 100644 --- a/compiler/typecheck/TcEnv.hs +++ b/compiler/typecheck/TcEnv.hs @@ -625,15 +625,18 @@ Consider data S = MkS (Proxy 'MkT) Is it ok to use the promoted data family instance constructor 'MkT' in -the data declaration for S? No, we don't allow this. It *might* make -sense, but at least it would mean that we'd have to interleave -typechecking instances and data types, whereas at present we do data -types *then* instances. +the data declaration for S (where both declarations live in the same module)? +No, we don't allow this. It *might* make sense, but at least it would mean that +we'd have to interleave typechecking instances and data types, whereas at +present we do data types *then* instances. So to check for this we put in the TcLclEnv a binding for all the family constructors, bound to AFamDataCon, so that if we trip over 'MkT' when type checking 'S' we'll produce a decent error message. +Trac #12088 describes this limitation. Of course, when MkT and S live in +different modules then all is well. + Note [Don't promote pattern synonyms] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We never promote pattern synonyms. diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index 3992a7e..6383b57 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -1077,7 +1077,8 @@ data PromotionErr | ClassPE -- Ditto Class | FamDataConPE -- Data constructor for a data family - -- See Note [AFamDataCon: not promoting data family constructors] in TcRnDriver + -- See Note [AFamDataCon: not promoting data family constructors] + -- in TcEnv. | PatSynPE -- Pattern synonyms -- See Note [Don't promote pattern synonyms] in TcEnv diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index e7a427f..2fcca7f 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -170,7 +170,7 @@ mkTypeableBinds | tc `elem` [runtimeRepTyCon, vecCountTyCon, vecElemTyCon] = False | otherwise = - (not (isFamInstTyCon tc) && isAlgTyCon tc) + isAlgTyCon tc || isDataFamilyTyCon tc || isClassTyCon tc @@ -243,12 +243,12 @@ todoForTyCons mod mod_id tycons = do } | 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 + -- Don't make bindings for data-family instance tycons. + -- Do, however, make them for their promoted datacon (see #13915). + , not $ isFamInstTyCon tc'' , Just rep_name <- pure $ tyConRepName_maybe tc'' , typeIsTypeable $ dropForAlls $ tyConKind tc'' ] diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index a2728ca..ce378bf 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -1061,13 +1061,14 @@ test('T12545', test('T13035', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 93249744, 5), + [(wordsize(64), 118665640, 5), # 2017-01-05 90595208 initial # 2017-01-19 95269000 Allow top-level string literals in Core # 2017-02-05 88806416 Probably OccAnal fixes # 2017-02-17 103890200 Type-indexed Typeable # 2017-02-25 98390488 Early inline patch # 2017-03-21 93249744 It's unclear + # 2017-07-19 118665640 Generate Typeable bindings for data instances ]), ], compile, diff --git a/testsuite/tests/typecheck/should_compile/T13915a.hs b/testsuite/tests/typecheck/should_compile/T13915a.hs new file mode 100644 index 0000000..484c9de --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13915a.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE TypeInType #-} +module Bug where + +import T13915a_Foo + +data Proxy (a :: k) +data S = MkS (Proxy 'MkT) diff --git a/testsuite/tests/rename/should_compile/T11164b.hs b/testsuite/tests/typecheck/should_compile/T13915a_Foo.hs similarity index 58% copy from testsuite/tests/rename/should_compile/T11164b.hs copy to testsuite/tests/typecheck/should_compile/T13915a_Foo.hs index abe65c4..1b5fd81 100644 --- a/testsuite/tests/rename/should_compile/T11164b.hs +++ b/testsuite/tests/typecheck/should_compile/T13915a_Foo.hs @@ -1,6 +1,5 @@ {-# LANGUAGE TypeFamilies #-} -module T11164b where - -import T11164a +module T13915a_Foo where +data family T a data instance T Int = MkT diff --git a/testsuite/tests/typecheck/should_compile/T13915b.hs b/testsuite/tests/typecheck/should_compile/T13915b.hs new file mode 100644 index 0000000..dd64b13 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13915b.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeInType #-} +module Foo where + +import Data.Typeable (Proxy(..), typeRep) + +data family T a +data instance T Int = MkT + +main :: IO () +main = print $ typeRep (Proxy :: Proxy MkT) diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 8f7996c..ee37b9a 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -568,3 +568,5 @@ test('T13822', normal, compile, ['']) test('T13871', normal, compile, ['']) test('T13879', normal, compile, ['']) test('T13881', normal, compile, ['']) +test('T13915a', normal, multimod_compile, ['T13915a', '-v0']) +test('T13915b', normal, compile, ['']) From git at git.haskell.org Thu Jul 20 10:56:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 10:56:09 +0000 (UTC) Subject: [commit: ghc] master: Spelling fixes (a273c73) Message-ID: <20170720105609.3054B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a273c735ca268988ee1550c248ba88b57a227cb9/ghc >--------------------------------------------------------------- commit a273c735ca268988ee1550c248ba88b57a227cb9 Author: Gabor Greif Date: Thu Jul 20 10:46:14 2017 +0200 Spelling fixes >--------------------------------------------------------------- a273c735ca268988ee1550c248ba88b57a227cb9 compiler/coreSyn/CoreSyn.hs | 2 +- compiler/coreSyn/CoreUnfold.hs | 2 +- compiler/coreSyn/CoreUtils.hs | 2 +- compiler/ghci/ByteCodeGen.hs | 8 ++++---- compiler/simplCore/SimplCore.hs | 2 +- compiler/simplCore/Simplify.hs | 2 +- compiler/specialise/Rules.hs | 2 +- compiler/typecheck/TcCanonical.hs | 2 +- compiler/typecheck/TcInstDcls.hs | 2 +- compiler/typecheck/TcSMonad.hs | 2 +- docs/users_guide/8.0.2-notes.rst | 2 +- testsuite/tests/typecheck/should_compile/tc189.hs | 2 +- 12 files changed, 15 insertions(+), 15 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 a273c735ca268988ee1550c248ba88b57a227cb9 From git at git.haskell.org Thu Jul 20 12:33:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 12:33:05 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Typeable: Ensure that promoted data family instance tycons get bindings (7252493) Message-ID: <20170720123305.81BE13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/725249344e28a58d2d827f38e630d0506f4e49cf/ghc >--------------------------------------------------------------- commit 725249344e28a58d2d827f38e630d0506f4e49cf Author: Ben Gamari Date: Wed Jul 19 19:33:00 2017 -0400 Typeable: Ensure that promoted data family instance tycons get bindings This fixes #13915, where the promoted tycons belonging to data family instances wouldn't get Typeable bindings, resulting in missing declarations. Test Plan: Validate with included testcases Reviewers: austin, simonpj Reviewed By: simonpj Subscribers: simonpj, RyanGlScott, rwbarton, thomie GHC Trac Issues: #13915 Differential Revision: https://phabricator.haskell.org/D3759 (cherry picked from commit cc839c57ff9c80b50d39e8e2e66a18674bab3486) >--------------------------------------------------------------- 725249344e28a58d2d827f38e630d0506f4e49cf compiler/typecheck/TcEnv.hs | 11 +++++++---- compiler/typecheck/TcRnTypes.hs | 3 ++- compiler/typecheck/TcTypeable.hs | 8 ++++---- testsuite/tests/perf/compiler/all.T | 3 ++- testsuite/tests/typecheck/should_compile/T13915a.hs | 7 +++++++ .../T11164b.hs => typecheck/should_compile/T13915a_Foo.hs} | 5 ++--- testsuite/tests/typecheck/should_compile/T13915b.hs | 11 +++++++++++ testsuite/tests/typecheck/should_compile/all.T | 2 ++ 8 files changed, 37 insertions(+), 13 deletions(-) diff --git a/compiler/typecheck/TcEnv.hs b/compiler/typecheck/TcEnv.hs index b69d1a6..6f02872 100644 --- a/compiler/typecheck/TcEnv.hs +++ b/compiler/typecheck/TcEnv.hs @@ -625,15 +625,18 @@ Consider data S = MkS (Proxy 'MkT) Is it ok to use the promoted data family instance constructor 'MkT' in -the data declaration for S? No, we don't allow this. It *might* make -sense, but at least it would mean that we'd have to interleave -typechecking instances and data types, whereas at present we do data -types *then* instances. +the data declaration for S (where both declarations live in the same module)? +No, we don't allow this. It *might* make sense, but at least it would mean that +we'd have to interleave typechecking instances and data types, whereas at +present we do data types *then* instances. So to check for this we put in the TcLclEnv a binding for all the family constructors, bound to AFamDataCon, so that if we trip over 'MkT' when type checking 'S' we'll produce a decent error message. +Trac #12088 describes this limitation. Of course, when MkT and S live in +different modules then all is well. + Note [Don't promote pattern synonyms] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We never promote pattern synonyms. diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index 882198f..10fd4e8 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -1047,7 +1047,8 @@ data PromotionErr | ClassPE -- Ditto Class | FamDataConPE -- Data constructor for a data family - -- See Note [AFamDataCon: not promoting data family constructors] in TcRnDriver + -- See Note [AFamDataCon: not promoting data family constructors] + -- in TcEnv. | PatSynPE -- Pattern synonyms -- See Note [Don't promote pattern synonyms] in TcEnv diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index 76d262c..ff0fb66 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -169,7 +169,7 @@ mkTypeableBinds | tc `elem` [runtimeRepTyCon, vecCountTyCon, vecElemTyCon] = False | otherwise = - (not (isFamInstTyCon tc) && isAlgTyCon tc) + isAlgTyCon tc || isDataFamilyTyCon tc || isClassTyCon tc @@ -242,12 +242,12 @@ todoForTyCons mod mod_id tycons = do } | 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 + -- Don't make bindings for data-family instance tycons. + -- Do, however, make them for their promoted datacon (see #13915). + , not $ isFamInstTyCon tc'' , Just rep_name <- pure $ tyConRepName_maybe tc'' , typeIsTypeable $ dropForAlls $ tyConKind tc'' ] diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 281615a..6fbde0d 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -1043,13 +1043,14 @@ test('T12234', test('T13035', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 93249744, 5), + [(wordsize(64), 118665640, 5), # 2017-01-05 90595208 initial # 2017-01-19 95269000 Allow top-level string literals in Core # 2017-02-05 88806416 Probably OccAnal fixes # 2017-02-17 103890200 Type-indexed Typeable # 2017-02-25 98390488 Early inline patch # 2017-03-21 93249744 It's unclear + # 2017-07-19 118665640 Generate Typeable bindings for data instances ]), ], compile, diff --git a/testsuite/tests/typecheck/should_compile/T13915a.hs b/testsuite/tests/typecheck/should_compile/T13915a.hs new file mode 100644 index 0000000..484c9de --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13915a.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE TypeInType #-} +module Bug where + +import T13915a_Foo + +data Proxy (a :: k) +data S = MkS (Proxy 'MkT) diff --git a/testsuite/tests/rename/should_compile/T11164b.hs b/testsuite/tests/typecheck/should_compile/T13915a_Foo.hs similarity index 58% copy from testsuite/tests/rename/should_compile/T11164b.hs copy to testsuite/tests/typecheck/should_compile/T13915a_Foo.hs index abe65c4..1b5fd81 100644 --- a/testsuite/tests/rename/should_compile/T11164b.hs +++ b/testsuite/tests/typecheck/should_compile/T13915a_Foo.hs @@ -1,6 +1,5 @@ {-# LANGUAGE TypeFamilies #-} -module T11164b where - -import T11164a +module T13915a_Foo where +data family T a data instance T Int = MkT diff --git a/testsuite/tests/typecheck/should_compile/T13915b.hs b/testsuite/tests/typecheck/should_compile/T13915b.hs new file mode 100644 index 0000000..dd64b13 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13915b.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeInType #-} +module Foo where + +import Data.Typeable (Proxy(..), typeRep) + +data family T a +data instance T Int = MkT + +main :: IO () +main = print $ typeRep (Proxy :: Proxy MkT) diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 7f72b03..c33f66f 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -558,3 +558,5 @@ test('T13804', normal, compile, ['']) test('T13871', normal, compile, ['']) test('T13879', normal, compile, ['']) test('T13881', normal, compile, ['']) +test('T13915a', normal, multimod_compile, ['T13915a', '-v0']) +test('T13915b', normal, compile, ['']) From git at git.haskell.org Thu Jul 20 12:33:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 12:33:08 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: testsuite: Ensure that hs_try_putmvar003 terminates (18460b3) Message-ID: <20170720123308.38CFB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/18460b3d0487fadefc0763f9b2129c46f45b3e15/ghc >--------------------------------------------------------------- commit 18460b3d0487fadefc0763f9b2129c46f45b3e15 Author: Ben Gamari Date: Wed Jul 19 15:06:02 2017 -0400 testsuite: Ensure that hs_try_putmvar003 terminates Test Plan: Validate Reviewers: austin, simonmar Reviewed By: simonmar Subscribers: simonmar, rwbarton, thomie GHC Trac Issues: #13434 Differential Revision: https://phabricator.haskell.org/D3724 (cherry picked from commit a051b555e32d7d8a08472e36be4cb08716d6d8ad) >--------------------------------------------------------------- 18460b3d0487fadefc0763f9b2129c46f45b3e15 testsuite/tests/concurrent/should_run/hs_try_putmvar003.hs | 4 ++-- testsuite/tests/concurrent/should_run/hs_try_putmvar003_c.c | 10 +++++++--- 2 files changed, 9 insertions(+), 5 deletions(-) diff --git a/testsuite/tests/concurrent/should_run/hs_try_putmvar003.hs b/testsuite/tests/concurrent/should_run/hs_try_putmvar003.hs index 4442698..d0c9739 100644 --- a/testsuite/tests/concurrent/should_run/hs_try_putmvar003.hs +++ b/testsuite/tests/concurrent/should_run/hs_try_putmvar003.hs @@ -51,7 +51,7 @@ makeExternalCall q = mask_ $ do data CallbackQueue foreign import ccall "mkCallbackQueue" - mkCallbackQueue :: Int -> IO (Ptr CallbackQueue) + mkCallbackQueue :: Int -> Int -> IO (Ptr CallbackQueue) foreign import ccall "destroyCallbackQueue" destroyCallbackQueue :: Ptr CallbackQueue -> IO () @@ -77,7 +77,7 @@ foreign export ccall callbackPutMVar :: StablePtr PrimMVar -> IO () experiment :: Bool -> Int -> Int -> Int -> IO () experiment use_foreign_export x y z = do mvars <- replicateM x $ async $ do - bracket (mkCallbackQueue (fromEnum use_foreign_export)) + bracket (mkCallbackQueue (fromEnum use_foreign_export) (z*y)) destroyCallbackQueue $ \q -> do mvars <- replicateM y $ async $ replicateM_ z $ void $ makeExternalCall q diff --git a/testsuite/tests/concurrent/should_run/hs_try_putmvar003_c.c b/testsuite/tests/concurrent/should_run/hs_try_putmvar003_c.c index aa65144..d67ca43 100644 --- a/testsuite/tests/concurrent/should_run/hs_try_putmvar003_c.c +++ b/testsuite/tests/concurrent/should_run/hs_try_putmvar003_c.c @@ -9,6 +9,9 @@ struct callback_queue { pthread_mutex_t lock; pthread_cond_t cond; int use_foreign_export; + // How many requests will be submitted to this queue? + // (e.g. n_threads * n_requests_per_thread) + int n_requests; struct callback *pending; }; @@ -24,7 +27,7 @@ void* callback(struct callback_queue *q) struct callback *cb; pthread_mutex_lock(&q->lock); - do { + for (int i=0; i < q->n_requests; i++) { if (q->pending == NULL) { pthread_cond_wait(&q->cond,&q->lock); } @@ -39,7 +42,7 @@ void* callback(struct callback_queue *q) } free(cb); } - } while (1); + } pthread_mutex_unlock(&q->lock); hs_thread_done(); @@ -48,7 +51,7 @@ void* callback(struct callback_queue *q) typedef void* threadfunc(void *); -struct callback_queue* mkCallbackQueue(int use_foreign_export) +struct callback_queue* mkCallbackQueue(int use_foreign_export, int n_requests) { struct callback_queue *q = malloc(sizeof(struct callback_queue)); pthread_t t; @@ -56,6 +59,7 @@ struct callback_queue* mkCallbackQueue(int use_foreign_export) pthread_cond_init(&q->cond, NULL); q->pending = NULL; q->use_foreign_export = use_foreign_export; + q->n_requests = n_requests; pthread_create(&t, NULL, (threadfunc*)callback, q); return q; } From git at git.haskell.org Thu Jul 20 12:33:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 12:33:10 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: dmdAnal: Ensure that ExnStr flag isn't dropped inappropriately (26f839f) Message-ID: <20170720123310.E57303A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/26f839f457ce1bf1a940a12e45c8137621ce1378/ghc >--------------------------------------------------------------- commit 26f839f457ce1bf1a940a12e45c8137621ce1378 Author: Ben Gamari Date: Wed Jul 19 15:07:52 2017 -0400 dmdAnal: Ensure that ExnStr flag isn't dropped inappropriately This fixes #13977 and consequently #13615. Here an optimization in the demand analyser was too liberal, causing us to drop the ExnStr flag and consequently resulting in incorrect demand signatures. This manifested as a segmentation fault in #13615 as we incorrectly concluded that an application of catchRetry# would bottom. Specifically, we had orElse' :: STM a -> STM a -> STM a orElse' x = catchRetry# x y where y = {- some action -} Where the catchRetry# primop places a demand of on its first argument. However, due to #13977 the demand analyser would assign a demand of on the first argument of orElse'. Note the missing `x`. case orElse' bottomingAction anotherAction of { x -> Just x } being transformed to, case orElse' bottomingAction anotherAction of {} by the simplifier. This would naturally blow up when orElse' returned at runtime, causing the segmentation fault described in #13615. Test Plan: Validate, perhaps add a testcase Reviewers: austin, simonpj Reviewed By: simonpj Subscribers: rwbarton, thomie GHC Trac Issues: #13977, #13615 Differential Revision: https://phabricator.haskell.org/D3756 (cherry picked from commit c940e3b92f4527ca59fcae93f36c869de3e7ccb9) >--------------------------------------------------------------- 26f839f457ce1bf1a940a12e45c8137621ce1378 compiler/basicTypes/Demand.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index 95c7b79..98b1915 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -1442,8 +1442,11 @@ postProcessDmdResult _ res = res postProcessDmdEnv :: DmdShell -> DmdEnv -> DmdEnv postProcessDmdEnv ds@(JD { sd = ss, ud = us }) env | Abs <- us = emptyDmdEnv - | Str _ _ <- ss - , Use One _ <- us = env -- Shell is a no-op + -- In this case (postProcessDmd ds) == id; avoid a redundant rebuild + -- of the environment. Be careful, bad things will happen if this doesn't + -- match postProcessDmd (see #13977). + | Str VanStr _ <- ss + , Use One _ <- us = env | otherwise = mapVarEnv (postProcessDmd ds) env -- For the Absent case just discard all usage information -- We only processed the thing at all to analyse the body From git at git.haskell.org Thu Jul 20 12:39:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 12:39:44 +0000 (UTC) Subject: [commit: ghc] master: Demand: Improve comments (eeb141d) Message-ID: <20170720123944.5931D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eeb141df7369d90f101c731adf12bbe46b42aa19/ghc >--------------------------------------------------------------- commit eeb141df7369d90f101c731adf12bbe46b42aa19 Author: Ben Gamari Date: Wed Jul 19 22:25:26 2017 -0400 Demand: Improve comments [skip-ci] Reviewers: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3737 >--------------------------------------------------------------- eeb141df7369d90f101c731adf12bbe46b42aa19 compiler/basicTypes/Demand.hs | 49 +++++++++++++++++++++++-------------------- 1 file changed, 26 insertions(+), 23 deletions(-) diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index 0262edc..dfff0a2 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -213,38 +213,40 @@ This confines the peculiarities to 'seq#', which is indeed rather essentially peculiar. -} --- Vanilla strictness domain +-- | Vanilla strictness domain data StrDmd - = HyperStr -- Hyper-strict - -- Bottom of the lattice - -- Note [HyperStr and Use demands] + = HyperStr -- ^ Hyper-strict (bottom of the lattice). + -- See Note [HyperStr and Use demands] - | SCall StrDmd -- Call demand + | SCall StrDmd -- ^ Call demand -- Used only for values of function type - | SProd [ArgStr] -- Product + | SProd [ArgStr] -- ^ Product -- Used only for values of product type -- Invariant: not all components are HyperStr (use HyperStr) -- not all components are Lazy (use HeadStr) - | HeadStr -- Head-Strict + | HeadStr -- ^ Head-Strict -- A polymorphic demand: used for values of all types, -- including a type variable deriving ( Eq, Show ) +-- | Strictness of a function argument. type ArgStr = Str StrDmd -data Str s = Lazy -- Lazy - -- Top of the lattice - | Str ExnStr s +-- | Strictness demand. +data Str s = Lazy -- ^ Lazy (top of the lattice) + | Str ExnStr s -- ^ Strict deriving ( Eq, Show ) +-- | How are exceptions handled for strict demands? data ExnStr -- See Note [Exceptions and strictness] - = VanStr -- "Vanilla" case, ordinary strictness + = VanStr -- ^ "Vanilla" case, ordinary strictness - | ExnStr -- (Str ExnStr d) means be strict like 'd' but then degrade - -- the Termination info ThrowsExn to Dunno + | ExnStr -- ^ @Str ExnStr d@ means be strict like @d@ but then degrade + -- the 'Termination' info 'ThrowsExn' to 'Dunno'. + -- e.g. the first argument of @catch@ has this strictness. deriving( Eq, Show ) -- Well-formedness preserving constructors for the Strictness domain @@ -376,27 +378,28 @@ splitStrProdDmd _ (SCall {}) = Nothing Abs -} --- Domain for genuine usage +-- | Domain for genuine usage data UseDmd - = UCall Count UseDmd -- Call demand for absence + = UCall Count UseDmd -- ^ Call demand for absence. -- Used only for values of function type - | UProd [ArgUse] -- Product + | UProd [ArgUse] -- ^ Product. -- Used only for values of product type -- See Note [Don't optimise UProd(Used) to Used] - -- [Invariant] Not all components are Abs - -- (in that case, use UHead) + -- + -- Invariant: Not all components are Abs + -- (in that case, use UHead) - | UHead -- May be used; but its sub-components are + | UHead -- ^ May be used but its sub-components are -- definitely *not* used. Roughly U(AAA) - -- Eg the usage of x in x `seq` e + -- e.g. the usage of @x@ in @x `seq` e@ -- A polymorphic demand: used for values of all types, -- including a type variable -- Since (UCall _ Abs) is ill-typed, UHead doesn't -- make sense for lambdas - | Used -- May be used; and its sub-components may be used - -- Top of the lattice + | Used -- ^ May be used and its sub-components may be used. + -- (top of the lattice) deriving ( Eq, Show ) -- Extended usage demand for absence and counting @@ -409,7 +412,7 @@ data Use u | Use Count u -- May be used with some cardinality deriving ( Eq, Show ) --- Abstract counting of usages +-- | Abstract counting of usages data Count = One | Many deriving ( Eq, Show ) From git at git.haskell.org Thu Jul 20 12:39:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 12:39:47 +0000 (UTC) Subject: [commit: ghc] master: Introduce -fcatch-bottoms (8e51bfc) Message-ID: <20170720123947.1ED373A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8e51bfc33c17aef41677a2b6189e3d4f31454cbc/ghc >--------------------------------------------------------------- commit 8e51bfc33c17aef41677a2b6189e3d4f31454cbc Author: Ben Gamari Date: Wed Jul 19 22:31:16 2017 -0400 Introduce -fcatch-bottoms This flag instructs the simplifier to emit ``error`` expressions in the continutation of empty case analyses (which should bottom and consequently not return). This is helpful when debugging demand analysis bugs which can sometimes manifest as segmentation faults. Test Plan: Validate Reviewers: simonpj, austin Subscribers: niteria, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3736 >--------------------------------------------------------------- 8e51bfc33c17aef41677a2b6189e3d4f31454cbc compiler/coreSyn/CorePrep.hs | 17 +++++++++++++++-- compiler/coreSyn/CoreUtils.hs | 1 + compiler/main/DynFlags.hs | 2 ++ docs/users_guide/debugging.rst | 7 +++++++ utils/mkUserGuidePart/Options/CompilerDebugging.hs | 6 ++++++ 5 files changed, 31 insertions(+), 2 deletions(-) diff --git a/compiler/coreSyn/CorePrep.hs b/compiler/coreSyn/CorePrep.hs index 5327acd..4f7a0da 100644 --- a/compiler/coreSyn/CorePrep.hs +++ b/compiler/coreSyn/CorePrep.hs @@ -645,8 +645,21 @@ cpeRhsE env (Case scrut bndr ty alts) ; let bndr1 = bndr `setIdUnfolding` evaldUnfolding -- Record that the case binder is evaluated in the alternatives ; (env', bndr2) <- cpCloneBndr env bndr1 - ; alts' <- mapM (sat_alt env') alts - ; return (floats, Case scrut' bndr2 ty alts') } + ; let alts' + -- This flag is intended to aid in debugging strictness + -- analysis bugs. These are particularly nasty to chase down as + -- they may manifest as segmentation faults. When this flag is + -- enabled we instead produce an 'error' expression to catch + -- the case where a function we think should bottom + -- unexpectedly returns. + | gopt Opt_CatchBottoms (cpe_dynFlags env) + , not (altsAreExhaustive alts) + = addDefault alts (Just err) + | otherwise = alts + where err = mkRuntimeErrorApp rUNTIME_ERROR_ID ty + "Bottoming expression returned" + ; alts'' <- mapM (sat_alt env') alts' + ; return (floats, Case scrut' bndr2 ty alts'') } where sat_alt env (con, bs, rhs) = do { (env2, bs') <- cpCloneBndrs env bs diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index eec524f..540a36e 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -30,6 +30,7 @@ module CoreUtils ( exprIsBig, exprIsConLike, rhsIsStatic, isCheapApp, isExpandableApp, exprIsLiteralString, exprIsTopLevelBindable, + altsAreExhaustive, -- * Equality cheapEqExpr, cheapEqExpr', eqExpr, diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 2be121e..5e33c2e 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -470,6 +470,7 @@ data GeneralFlag | Opt_CprAnal | Opt_WorkerWrapper | Opt_SolveConstantDicts + | Opt_CatchBottoms -- Interface files | Opt_IgnoreInterfacePragmas @@ -3778,6 +3779,7 @@ fFlagsDeps = [ flagSpec "version-macros" Opt_VersionMacros, flagSpec "worker-wrapper" Opt_WorkerWrapper, flagSpec "solve-constant-dicts" Opt_SolveConstantDicts, + flagSpec "catch-bottoms" Opt_CatchBottoms, flagSpec "show-warning-groups" Opt_ShowWarnGroups, flagSpec "hide-source-paths" Opt_HideSourcePaths, flagSpec "show-hole-constraints" Opt_ShowHoleConstraints, diff --git a/docs/users_guide/debugging.rst b/docs/users_guide/debugging.rst index fd4adc7..af937ae 100644 --- a/docs/users_guide/debugging.rst +++ b/docs/users_guide/debugging.rst @@ -389,6 +389,13 @@ Checking for consistency instead of ``undef`` in calls. This makes it easier to catch subtle code generator and runtime system bugs (e.g. see :ghc-ticket:`11487`). +.. ghc-flag:: -fcatch-bottoms + + Instructs the simplifier to emit ``error`` expressions in the continuation + of empty case analyses (which should bottom and consequently not return). + This is helpful when debugging demand analysis bugs which can sometimes + manifest as segmentation faults. + .. _checking-determinism: Checking for determinism diff --git a/utils/mkUserGuidePart/Options/CompilerDebugging.hs b/utils/mkUserGuidePart/Options/CompilerDebugging.hs index 9704020..e68216b 100644 --- a/utils/mkUserGuidePart/Options/CompilerDebugging.hs +++ b/utils/mkUserGuidePart/Options/CompilerDebugging.hs @@ -278,4 +278,10 @@ compilerDebuggingOptions = "Takes a string argument." , flagType = DynamicFlag } + , flag { flagName = "-fcatch-bottoms" + , flagDescription = + "Insert ``error`` expressions after bottoming expressions; useful "++ + "when debugging the compiler." + , flagType = DynamicFlag + } ] From git at git.haskell.org Thu Jul 20 14:16:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 14:16:02 +0000 (UTC) Subject: [commit: ghc] wip/zyla-T8095: Enabled -fomit-type-family-coercions in validate build (584a346) Message-ID: <20170720141602.C0EB13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/zyla-T8095 Link : http://ghc.haskell.org/trac/ghc/changeset/584a3460ace69efbf5378db2c6f5a24b45856486/ghc >--------------------------------------------------------------- commit 584a3460ace69efbf5378db2c6f5a24b45856486 Author: Matthew Pickering Date: Thu Jul 20 14:14:41 2017 +0000 Enabled -fomit-type-family-coercions in validate build >--------------------------------------------------------------- 584a3460ace69efbf5378db2c6f5a24b45856486 mk/flavours/validate.mk | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/mk/flavours/validate.mk b/mk/flavours/validate.mk index 2ff7c20..5549a6f 100644 --- a/mk/flavours/validate.mk +++ b/mk/flavours/validate.mk @@ -1,8 +1,8 @@ SRC_HC_OPTS = -O0 -H64m SRC_HC_OPTS_STAGE1 = -fllvm-fill-undef-with-garbage # See Trac 11487 GhcStage1HcOpts = -O -DDEBUG -GhcStage2HcOpts = -O -dcore-lint -dno-debug-output -GhcLibHcOpts = -O -dcore-lint -dno-debug-output +GhcStage2HcOpts = -O -dcore-lint -dno-debug-output -fomit-type-family-coercions +GhcLibHcOpts = -O -dcore-lint -dno-debug-output -fomit-type-family-coercions BUILD_PROF_LIBS = NO SplitObjs = NO SplitSections = NO From git at git.haskell.org Thu Jul 20 16:04:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 16:04:57 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Pipe stdin directly to process (c9c762d) Message-ID: <20170720160457.DF8143A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c9c762dc0a782cf66aa3bf5cccfa7f0d16a37696/ghc >--------------------------------------------------------------- commit c9c762dc0a782cf66aa3bf5cccfa7f0d16a37696 Author: Ben Gamari Date: Thu Jul 20 08:40:49 2017 -0400 testsuite: Pipe stdin directly to process Previously the driver would read the stdin content from the source file and then write it to the subprocess' stdin. We now simply open the stdin file and provide that handle to the subprocess as its stdin Test Plan: Validate Reviewers: austin Subscribers: rwbarton, thomie, goldfire Differential Revision: https://phabricator.haskell.org/D3735 >--------------------------------------------------------------- c9c762dc0a782cf66aa3bf5cccfa7f0d16a37696 testsuite/driver/testlib.py | 16 +++++----------- 1 file changed, 5 insertions(+), 11 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 4212214..26e3d17 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1792,15 +1792,7 @@ def runCmd(cmd, stdin=None, stdout=None, stderr=None, timeout_multiplier=1.0, pr # declare the buffers to a default stdin_buffer = None - # ***** IMPORTANT ***** - # We have to treat input and output as - # just binary data here. Don't try to decode - # it to a string, since we have tests that actually - # feed malformed utf-8 to see how GHC handles it. - if stdin: - with io.open(stdin, 'rb') as f: - stdin_buffer = f.read() - + stdin_file = io.open(stdin, 'rb') if stdin else None stdout_buffer = b'' stderr_buffer = b'' @@ -1815,12 +1807,14 @@ def runCmd(cmd, stdin=None, stdout=None, stderr=None, timeout_multiplier=1.0, pr # to invoke the Bourne shell r = subprocess.Popen([timeout_prog, timeout, cmd], - stdin=subprocess.PIPE, + stdin=stdin_file, stdout=subprocess.PIPE, stderr=hStdErr) - stdout_buffer, stderr_buffer = r.communicate(stdin_buffer) + stdout_buffer, stderr_buffer = r.communicate() finally: + if stdin_file: + stdin_file.close() if config.verbose >= 1 and print_output >= 1: if stdout_buffer: sys.stdout.buffer.write(stdout_buffer) From git at git.haskell.org Thu Jul 20 16:05:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 16:05:00 +0000 (UTC) Subject: [commit: ghc] master: arcconfig: Set project ruleset to use master merge-base by default (a85a595) Message-ID: <20170720160500.A2BA13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a85a5959d2c00dff609e5945787803423bf3423e/ghc >--------------------------------------------------------------- commit a85a5959d2c00dff609e5945787803423bf3423e Author: Ben Gamari Date: Thu Jul 20 08:41:09 2017 -0400 arcconfig: Set project ruleset to use master merge-base by default Reviewers: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3728 >--------------------------------------------------------------- a85a5959d2c00dff609e5945787803423bf3423e .arcconfig | 1 + 1 file changed, 1 insertion(+) diff --git a/.arcconfig b/.arcconfig index c886789..29021b3 100644 --- a/.arcconfig +++ b/.arcconfig @@ -2,6 +2,7 @@ "project.name" : "ghc", "repository.callsign" : "GHC", "phabricator.uri" : "https://phabricator.haskell.org", + "base" : "git:merge-base(origin/master), arc:prompt", "load": [ ".arc-linters/arcanist-external-json-linter" From git at git.haskell.org Thu Jul 20 16:05:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 16:05:03 +0000 (UTC) Subject: [commit: ghc] master: Fix busy-wait in SysTools.builderMainLoop (194384f) Message-ID: <20170720160503.5D0FA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/194384f1318e0553e0c5ce621ca0903b55862eb3/ghc >--------------------------------------------------------------- commit 194384f1318e0553e0c5ce621ca0903b55862eb3 Author: Douglas Wilson Date: Thu Jul 20 08:48:12 2017 -0400 Fix busy-wait in SysTools.builderMainLoop Test T13701 was failing sporadically. The problem manifested while the test was run on a system under load. Profiling showed the increased allocations were in SysTools.builderMainLoop.loop, during calls to the assembler. This was due to loop effectively busy-waiting from when both stdin and stderr handles were closed, until getProcessExitCode succeeded. This is fixed by removing exit code handling from loop. We now wait for loop to finish, then read the exit code with waitForProcess. Some exception safety is added: the readerProc threads will now be killed and the handles will be closed if an exception is thrown. A TODO saying that threads dying is not accounted for is removed. I believe that this case is handled by readerProc sending EOF in a finally clause. Test Plan: Replicate test failures using procedure on the ticket, verify that they do not occur with this patch. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13987 Differential Revision: https://phabricator.haskell.org/D3748 >--------------------------------------------------------------- 194384f1318e0553e0c5ce621ca0903b55862eb3 compiler/main/SysTools.hs | 96 ++++++++++++++++++++----------------- testsuite/tests/perf/compiler/all.T | 3 +- 2 files changed, 55 insertions(+), 44 deletions(-) diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs index 0a19feb..3d16124 100644 --- a/compiler/main/SysTools.hs +++ b/compiler/main/SysTools.hs @@ -1134,50 +1134,60 @@ builderMainLoop :: DynFlags -> (String -> String) -> FilePath -> IO ExitCode builderMainLoop dflags filter_fn pgm real_args mb_env = do chan <- newChan - (hStdIn, hStdOut, hStdErr, hProcess) <- runInteractiveProcess pgm real_args Nothing mb_env - - -- and run a loop piping the output from the compiler to the log_action in DynFlags - hSetBuffering hStdOut LineBuffering - hSetBuffering hStdErr LineBuffering - _ <- forkIO (readerProc chan hStdOut filter_fn) - _ <- forkIO (readerProc chan hStdErr filter_fn) - -- we don't want to finish until 2 streams have been completed - -- (stdout and stderr) - -- nor until 1 exit code has been retrieved. - rc <- loop chan hProcess (2::Integer) (1::Integer) ExitSuccess - -- after that, we're done here. - hClose hStdIn - hClose hStdOut - hClose hStdErr - return rc + + -- We use a mask here rather than a bracket because we want + -- to distinguish between cleaning up with and without an + -- exception. This is to avoid calling terminateProcess + -- unless an exception was raised. + let safely inner = mask $ \restore -> do + -- acquire + (hStdIn, hStdOut, hStdErr, hProcess) <- restore $ + runInteractiveProcess pgm real_args Nothing mb_env + let cleanup_handles = do + hClose hStdIn + hClose hStdOut + hClose hStdErr + r <- try $ restore $ do + hSetBuffering hStdOut LineBuffering + hSetBuffering hStdErr LineBuffering + let make_reader_proc h = forkIO $ readerProc chan h filter_fn + bracketOnError (make_reader_proc hStdOut) killThread $ \_ -> + bracketOnError (make_reader_proc hStdErr) killThread $ \_ -> + inner hProcess + case r of + -- onException + Left (SomeException e) -> do + terminateProcess hProcess + cleanup_handles + throw e + -- cleanup when there was no exception + Right s -> do + cleanup_handles + return s + safely $ \h -> do + -- we don't want to finish until 2 streams have been complete + -- (stdout and stderr) + log_loop chan (2 :: Integer) + -- after that, we wait for the process to finish and return the exit code. + waitForProcess h where - -- status starts at zero, and increments each time either - -- a reader process gets EOF, or the build proc exits. We wait - -- for all of these to happen (status==3). - -- ToDo: we should really have a contingency plan in case any of - -- the threads dies, such as a timeout. - loop _ _ 0 0 exitcode = return exitcode - loop chan hProcess t p exitcode = do - mb_code <- if p > 0 - then getProcessExitCode hProcess - else return Nothing - case mb_code of - Just code -> loop chan hProcess t (p-1) code - Nothing - | t > 0 -> do - msg <- readChan chan - case msg of - BuildMsg msg -> do - putLogMsg dflags NoReason SevInfo noSrcSpan - (defaultUserStyle dflags) msg - loop chan hProcess t p exitcode - BuildError loc msg -> do - putLogMsg dflags NoReason SevError (mkSrcSpan loc loc) - (defaultUserStyle dflags) msg - loop chan hProcess t p exitcode - EOF -> - loop chan hProcess (t-1) p exitcode - | otherwise -> loop chan hProcess t p exitcode + -- t starts at the number of streams we're listening to (2) decrements each + -- time a reader process sends EOF. We are safe from looping forever if a + -- reader thread dies, because they send EOF in a finally handler. + log_loop _ 0 = return () + log_loop chan t = do + msg <- readChan chan + case msg of + BuildMsg msg -> do + putLogMsg dflags NoReason SevInfo noSrcSpan + (defaultUserStyle dflags) msg + log_loop chan t + BuildError loc msg -> do + putLogMsg dflags NoReason SevError (mkSrcSpan loc loc) + (defaultUserStyle dflags) msg + log_loop chan t + EOF -> + log_loop chan (t-1) readerProc :: Chan BuildMessage -> Handle -> (String -> String) -> IO () readerProc chan hdl filter_fn = diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index ce378bf..0389271 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -1132,11 +1132,12 @@ test('MultiLayerModules', test('T13701', [ compiler_stats_num_field('bytes allocated', [(platform('x86_64-apple-darwin'), 2217187888, 10), - (platform('x86_64-unknown-linux'), 2412223768, 10), + (platform('x86_64-unknown-linux'), 2133380768, 10), # initial: 2511285600 # 2017-06-23: 2188045288 treat banged variable bindings as FunBinds # 2017-07-11: 2187920960 # 2017-07-12: 2412223768 inconsistency between Ben's machine and Harbormaster? + # 2017-07-17: 2133380768 Resolved the issue causing the inconsistencies in this test ]), pre_cmd('./genT13701'), extra_files(['genT13701']), From git at git.haskell.org Thu Jul 20 16:05:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 16:05:07 +0000 (UTC) Subject: [commit: ghc] master: Make IfaceAxiom typechecking lazier. (fdb6a5b) Message-ID: <20170720160507.634AE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fdb6a5bfd545094782fb539951b561ac2467443d/ghc >--------------------------------------------------------------- commit fdb6a5bfd545094782fb539951b561ac2467443d Author: Edward Z. Yang Date: Thu Jul 20 11:30:46 2017 -0400 Make IfaceAxiom typechecking lazier. Fixes #13803, but adds a note about a yet to be fixed #13981. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #13803 Differential Revision: https://phabricator.haskell.org/D3742 >--------------------------------------------------------------- fdb6a5bfd545094782fb539951b561ac2467443d compiler/iface/TcIface.hs | 9 ++- compiler/typecheck/FamInst.hs | 69 ++++++++++++++++++---- testsuite/tests/driver/T13803/D.hs | 5 ++ testsuite/tests/driver/T13803/E.hs | 11 ++++ testsuite/tests/driver/T13803/E.hs-boot | 1 + .../tests/{cabal/pkg02 => driver/T13803}/Makefile | 2 + testsuite/tests/driver/T13803/T13803.stdout | 5 ++ testsuite/tests/driver/T13803/Y.hs | 6 ++ testsuite/tests/driver/T13803/Y.hs-boot | 3 + testsuite/tests/driver/T13803/all.T | 4 ++ 10 files changed, 103 insertions(+), 12 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fdb6a5bfd545094782fb539951b561ac2467443d From git at git.haskell.org Thu Jul 20 16:05:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 16:05:10 +0000 (UTC) Subject: [commit: ghc] master: Interpreter.c: use macros to access/modify Sp (5469ac8) Message-ID: <20170720160510.2A24C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5469ac86f9cc9e83b93ed34ca13f0a4f58f4a9a6/ghc >--------------------------------------------------------------- commit 5469ac86f9cc9e83b93ed34ca13f0a4f58f4a9a6 Author: Michal Terepeta Date: Thu Jul 20 11:30:54 2017 -0400 Interpreter.c: use macros to access/modify Sp This is another step in fixing #13825 (based on D38 by Simon Marlow). This commit adds a few macros for accessing and modifying `Sp` (interpreter stack) and will be useful to allow sub-word indexing/pushing. (but that will be a separate change, this commit should introduce no changes in behavior) Signed-off-by: Michal Terepeta Test Plan: ./validate Reviewers: bgamari, simonmar, austin, erikd Reviewed By: bgamari, erikd Subscribers: rwbarton, thomie GHC Trac Issues: #13825 Differential Revision: https://phabricator.haskell.org/D3744 >--------------------------------------------------------------- 5469ac86f9cc9e83b93ed34ca13f0a4f58f4a9a6 rts/Interpreter.c | 467 ++++++++++++++++++++++++++++-------------------------- 1 file changed, 240 insertions(+), 227 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 5469ac86f9cc9e83b93ed34ca13f0a4f58f4a9a6 From git at git.haskell.org Thu Jul 20 16:05:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 16:05:12 +0000 (UTC) Subject: [commit: ghc] master: rts: Claim AP_STACK before adjusting Sp (bade356) Message-ID: <20170720160512.DCA493A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bade356f79d44c9f6e8918a89d9ffac7f5608dbf/ghc >--------------------------------------------------------------- commit bade356f79d44c9f6e8918a89d9ffac7f5608dbf Author: Ben Gamari Date: Thu Jul 20 11:33:51 2017 -0400 rts: Claim AP_STACK before adjusting Sp In the fix to #13615 we introduced some logic to atomically blackhole AP_STACKs closures upon entry. However, this logic was placed *after* a stack pointer adjustment. This meant that if someone else beat us to blackholing the AP_STACK we would suspend the thread with uninitialized content on the stack. This would then later blow up when threadPaused attempted to walk the stack, hence #13970. Silly bug but still cost lots of head-scratching to find. Thanks to albertov for the great repro. Fixes #13970. Bug originally introduced by the fix to #13615. Reviewers: austin, erikd, simonmar Reviewed By: erikd, simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13970, #13615 Differential Revision: https://phabricator.haskell.org/D3760 >--------------------------------------------------------------- bade356f79d44c9f6e8918a89d9ffac7f5608dbf rts/Apply.cmm | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/rts/Apply.cmm b/rts/Apply.cmm index 64f0a9b..ffcd035 100644 --- a/rts/Apply.cmm +++ b/rts/Apply.cmm @@ -637,11 +637,6 @@ INFO_TABLE(stg_AP_STACK,/*special layout*/0,0,AP_STACK,"AP_STACK","AP_STACK") * than continuing to evaluate the now-defunct closure. */ STK_CHK_ENTER(WDS(Words) + SIZEOF_StgUpdateFrame + WDS(AP_STACK_SPLIM), R1); - /* ensure there is at least AP_STACK_SPLIM words of headroom available - * after unpacking the AP_STACK. See bug #1466 */ - - PUSH_UPD_FRAME(Sp - SIZEOF_StgUpdateFrame, R1); - Sp = Sp - SIZEOF_StgUpdateFrame - WDS(Words); /* * It is imperative that we blackhole lest we may duplicate computation which @@ -657,6 +652,11 @@ INFO_TABLE(stg_AP_STACK,/*special layout*/0,0,AP_STACK,"AP_STACK","AP_STACK") prim_write_barrier; SET_INFO(ap, __stg_EAGER_BLACKHOLE_info); + /* ensure there is at least AP_STACK_SPLIM words of headroom available + * after unpacking the AP_STACK. See bug #1466 */ + PUSH_UPD_FRAME(Sp - SIZEOF_StgUpdateFrame, R1); + Sp = Sp - SIZEOF_StgUpdateFrame - WDS(Words); + TICK_ENT_AP(); LDV_ENTER(ap); ENTER_CCS_THUNK(ap); From git at git.haskell.org Thu Jul 20 16:05:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 16:05:15 +0000 (UTC) Subject: [commit: ghc] master: distrib/configure: Canonicalize triples (1480080) Message-ID: <20170720160515.99BF53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1480080b31e9f7cd47ca7b677455b3558b0da2bc/ghc >--------------------------------------------------------------- commit 1480080b31e9f7cd47ca7b677455b3558b0da2bc Author: Ben Gamari Date: Thu Jul 20 11:34:00 2017 -0400 distrib/configure: Canonicalize triples Previously we failed to do this, which meant that the bindist's configure would fail when passed --target (as you may need to do when installing an armv7 bindist on an aarch64 machine, for instance). Reviewers: hvr, erikd, austin Reviewed By: hvr Subscribers: rwbarton, thomie GHC Trac Issues: #13934 Differential Revision: https://phabricator.haskell.org/D3761 >--------------------------------------------------------------- 1480080b31e9f7cd47ca7b677455b3558b0da2bc distrib/configure.ac.in | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index a15b4a5..314bb3a 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -13,6 +13,13 @@ dnl-------------------------------------------------------------------- FP_GMP bootstrap_target=@TargetPlatform@ + +# We have to run these unconditionally as FPTOOLS_SET_PLATFORM_VARS wants the +# values it computes. +AC_CANONICAL_BUILD +AC_CANONICAL_HOST +AC_CANONICAL_TARGET + FPTOOLS_SET_PLATFORM_VARS # Requires FPTOOLS_SET_PLATFORM_VARS to be run first. From git at git.haskell.org Thu Jul 20 16:05:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 16:05:19 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add test for #13916 (b2d3ec3) Message-ID: <20170720160519.04E023A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b2d3ec370b97fe5f448e8f1d4e0b7374c63c60a8/ghc >--------------------------------------------------------------- commit b2d3ec370b97fe5f448e8f1d4e0b7374c63c60a8 Author: Ben Gamari Date: Thu Jul 20 11:43:06 2017 -0400 testsuite: Add test for #13916 >--------------------------------------------------------------- b2d3ec370b97fe5f448e8f1d4e0b7374c63c60a8 testsuite/tests/concurrent/should_run/T13916.hs | 33 +++++ .../tests/concurrent/should_run/T13916_Bracket.hs | 135 +++++++++++++++++++++ testsuite/tests/concurrent/should_run/all.T | 1 + 3 files changed, 169 insertions(+) diff --git a/testsuite/tests/concurrent/should_run/T13916.hs b/testsuite/tests/concurrent/should_run/T13916.hs new file mode 100755 index 0000000..e81aabb --- /dev/null +++ b/testsuite/tests/concurrent/should_run/T13916.hs @@ -0,0 +1,33 @@ +module Main where + +import Data.IORef +import System.IO.Unsafe +import Control.Concurrent.STM +import Control.Concurrent.Async +import Control.Concurrent +import System.IO +import System.Directory +import System.FilePath +import T13916_Bracket + +type Thing = MVar Bool + +main :: IO () +main = do + withEnvCache limit spawner $ \cache -> + forConcurrently_ [1..1000 :: Int] $ \n -> withEnv cache (\handle -> put handle n) + where + limit :: Limit + limit = Hard 1 + + put handle n = return () + +spawner :: Spawner Thing +spawner = Spawner + { maker = mkhandle + , killer = \thing -> takeMVar thing >> putMVar thing True + , isDead = \thing -> readMVar thing + } + +mkhandle :: IO Thing +mkhandle = newMVar False diff --git a/testsuite/tests/concurrent/should_run/T13916_Bracket.hs b/testsuite/tests/concurrent/should_run/T13916_Bracket.hs new file mode 100755 index 0000000..340cbb3 --- /dev/null +++ b/testsuite/tests/concurrent/should_run/T13916_Bracket.hs @@ -0,0 +1,135 @@ +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE RecordWildCards #-} +{- | +Module : Bracket +Description : Handling multiple environments with bracket-like apis +Maintainer : robertkennedy at clearwateranalytics.com +Stability : stable + +This module is meant for ie Sql or mongo connections, where you may wish for some number of easy to grab +environments. In particular, this assumes your connection has some initialization/release functions + +This module creates bugs with any optimizations enabled. The bugs do not occur if the program is in the same +module. +-} +module Bracket ( + -- * Data Types + Spawner(..), Limit(..), Cache, + -- * Usage + withEnvCache, withEnv + ) where + +import Control.Concurrent.STM +import Control.Concurrent.STM.TSem +import Control.Exception hiding (handle) +import Control.Monad +import Data.Vector (Vector) +import qualified Data.Vector as Vector + +-- * Data Types +-- | Tells the program how many environments it is allowed to spawn. +-- A `Lax` limit will spawn extra connections if the `Cache` is empty, +-- while a `Hard` limit will not spawn any more than the given number of connections simultaneously. +-- +-- @since 0.3.7 +data Limit = Hard {getLimit :: {-# unpack #-} !Int} + +data Spawner env = Spawner + { maker :: IO env + , killer :: env -> IO () + , isDead :: env -> IO Bool + } + +type VCache env = Vector (TMVar env) +data Cache env = Unlimited { spawner :: Spawner env + , vcache :: !(VCache env) + } + | Limited { spawner :: Spawner env + , vcache :: !(VCache env) + , envsem :: TSem + } + +-- ** Initialization +withEnvCache :: Limit -> Spawner env -> (Cache env -> IO a) -> IO a +withEnvCache limit spawner = bracket starter releaseCache + where starter = case limit of + Hard n -> Limited spawner <$> initializeEmptyCache n <*> atomically (newTSem n) + +-- ** Using a single value +withEnv :: Cache env -> (env -> IO a) -> IO a +withEnv cache = case cache of + Unlimited{..} -> withEnvUnlimited spawner vcache + Limited{..} -> withEnvLimited spawner vcache envsem + +-- *** Unlimited +-- | Takes an env and returns it on completion of the function. +-- If all envs are already taken or closed, this will spin up a new env. +-- When the function finishes, this will attempt to put the env into the cache. If it cannot, +-- it will kill the env. Note this can lead to many concurrent connections. +-- +-- @since 0.3.5 +withEnvUnlimited :: Spawner env -> VCache env -> (env -> IO a) -> IO a +withEnvUnlimited Spawner{..} cache = bracket taker putter + where + taker = do + mpipe <- atomically $ tryTakeEnv cache + case mpipe of + Nothing -> maker + Just env -> isDead env >>= \b -> if not b then return env else killer env >> maker + + putter env = do + accepted <- atomically $ tryPutEnv cache env + unless accepted $ killer env + +-- *** Limited +-- | Takes an env and returns it on completion of the function. +-- If all envs are already taken, this will wait. This should have a constant number of environments +-- +-- @since 0.3.6 +withEnvLimited :: Spawner env -> VCache env -> TSem -> (env -> IO a) -> IO a +withEnvLimited spawner vcache envsem = bracket taker putter + where + taker = limitMakeEnv spawner vcache envsem + putter env = atomically $ putEnv vcache env + +limitMakeEnv :: Spawner env -> VCache env -> TSem -> IO env +limitMakeEnv Spawner{..} vcache envsem = go + where + go = do + eenvpermission <- atomically $ ( Left <$> takeEnv vcache ) + `orElse` ( Right <$> waitTSem envsem ) + case eenvpermission of + Right () -> maker + Left env -> do + -- Given our env, we check if it's dead. If it's not, we are done and return it. + -- If it is dead, we release it, signal that a new env can be created, and then recurse + isdead <- isDead env + if not isdead then return env + else do + killer env + atomically $ signalTSem envsem + go + +-- * Low level +initializeEmptyCache :: Int -> IO (VCache env) +initializeEmptyCache n | n < 1 = return mempty + | otherwise = Vector.replicateM n newEmptyTMVarIO + +takeEnv :: VCache env -> STM env +takeEnv = Vector.foldl folding retry + where folding m stmenv = m `orElse` takeTMVar stmenv + +tryTakeEnv :: VCache env -> STM (Maybe env) +tryTakeEnv cache = (Just <$> takeEnv cache) `orElse` pure Nothing + +putEnv :: VCache env -> env -> STM () +putEnv cache env = Vector.foldl folding retry cache + where folding m stmenv = m `orElse` putTMVar stmenv env + +tryPutEnv :: VCache env -> env -> STM Bool +tryPutEnv cache env = (putEnv cache env *> return True) `orElse` pure False + +releaseCache :: Cache env -> IO () +releaseCache cache = Vector.mapM_ qkRelease (vcache cache) + where qkRelease tenv = atomically (tryTakeTMVar tenv) + >>= maybe (return ()) (killer $ spawner cache) diff --git a/testsuite/tests/concurrent/should_run/all.T b/testsuite/tests/concurrent/should_run/all.T index 69b8ad7..abac22a 100644 --- a/testsuite/tests/concurrent/should_run/all.T +++ b/testsuite/tests/concurrent/should_run/all.T @@ -284,3 +284,4 @@ test('hs_try_putmvar003', # Check forkIO exception determinism under optimization test('T13330', normal, compile_and_run, ['-O']) +test('T13916', normal, compile_and_run, ['-O2']) From git at git.haskell.org Thu Jul 20 16:06:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 16:06:25 +0000 (UTC) Subject: [commit: ghc] master: Revert "testsuite: Add test for #13916" (ccac387) Message-ID: <20170720160625.860B63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ccac387bd90da8e1b6998e8480897a0bf0694310/ghc >--------------------------------------------------------------- commit ccac387bd90da8e1b6998e8480897a0bf0694310 Author: Ben Gamari Date: Thu Jul 20 12:06:03 2017 -0400 Revert "testsuite: Add test for #13916" This reverts commit b2d3ec370b97fe5f448e8f1d4e0b7374c63c60a8. Didn't mean to push this one. >--------------------------------------------------------------- ccac387bd90da8e1b6998e8480897a0bf0694310 testsuite/tests/concurrent/should_run/T13916.hs | 33 ----- .../tests/concurrent/should_run/T13916_Bracket.hs | 135 --------------------- testsuite/tests/concurrent/should_run/all.T | 1 - 3 files changed, 169 deletions(-) diff --git a/testsuite/tests/concurrent/should_run/T13916.hs b/testsuite/tests/concurrent/should_run/T13916.hs deleted file mode 100755 index e81aabb..0000000 --- a/testsuite/tests/concurrent/should_run/T13916.hs +++ /dev/null @@ -1,33 +0,0 @@ -module Main where - -import Data.IORef -import System.IO.Unsafe -import Control.Concurrent.STM -import Control.Concurrent.Async -import Control.Concurrent -import System.IO -import System.Directory -import System.FilePath -import T13916_Bracket - -type Thing = MVar Bool - -main :: IO () -main = do - withEnvCache limit spawner $ \cache -> - forConcurrently_ [1..1000 :: Int] $ \n -> withEnv cache (\handle -> put handle n) - where - limit :: Limit - limit = Hard 1 - - put handle n = return () - -spawner :: Spawner Thing -spawner = Spawner - { maker = mkhandle - , killer = \thing -> takeMVar thing >> putMVar thing True - , isDead = \thing -> readMVar thing - } - -mkhandle :: IO Thing -mkhandle = newMVar False diff --git a/testsuite/tests/concurrent/should_run/T13916_Bracket.hs b/testsuite/tests/concurrent/should_run/T13916_Bracket.hs deleted file mode 100755 index 340cbb3..0000000 --- a/testsuite/tests/concurrent/should_run/T13916_Bracket.hs +++ /dev/null @@ -1,135 +0,0 @@ -{-# LANGUAGE RankNTypes #-} -{-# LANGUAGE RecordWildCards #-} -{- | -Module : Bracket -Description : Handling multiple environments with bracket-like apis -Maintainer : robertkennedy at clearwateranalytics.com -Stability : stable - -This module is meant for ie Sql or mongo connections, where you may wish for some number of easy to grab -environments. In particular, this assumes your connection has some initialization/release functions - -This module creates bugs with any optimizations enabled. The bugs do not occur if the program is in the same -module. --} -module Bracket ( - -- * Data Types - Spawner(..), Limit(..), Cache, - -- * Usage - withEnvCache, withEnv - ) where - -import Control.Concurrent.STM -import Control.Concurrent.STM.TSem -import Control.Exception hiding (handle) -import Control.Monad -import Data.Vector (Vector) -import qualified Data.Vector as Vector - --- * Data Types --- | Tells the program how many environments it is allowed to spawn. --- A `Lax` limit will spawn extra connections if the `Cache` is empty, --- while a `Hard` limit will not spawn any more than the given number of connections simultaneously. --- --- @since 0.3.7 -data Limit = Hard {getLimit :: {-# unpack #-} !Int} - -data Spawner env = Spawner - { maker :: IO env - , killer :: env -> IO () - , isDead :: env -> IO Bool - } - -type VCache env = Vector (TMVar env) -data Cache env = Unlimited { spawner :: Spawner env - , vcache :: !(VCache env) - } - | Limited { spawner :: Spawner env - , vcache :: !(VCache env) - , envsem :: TSem - } - --- ** Initialization -withEnvCache :: Limit -> Spawner env -> (Cache env -> IO a) -> IO a -withEnvCache limit spawner = bracket starter releaseCache - where starter = case limit of - Hard n -> Limited spawner <$> initializeEmptyCache n <*> atomically (newTSem n) - --- ** Using a single value -withEnv :: Cache env -> (env -> IO a) -> IO a -withEnv cache = case cache of - Unlimited{..} -> withEnvUnlimited spawner vcache - Limited{..} -> withEnvLimited spawner vcache envsem - --- *** Unlimited --- | Takes an env and returns it on completion of the function. --- If all envs are already taken or closed, this will spin up a new env. --- When the function finishes, this will attempt to put the env into the cache. If it cannot, --- it will kill the env. Note this can lead to many concurrent connections. --- --- @since 0.3.5 -withEnvUnlimited :: Spawner env -> VCache env -> (env -> IO a) -> IO a -withEnvUnlimited Spawner{..} cache = bracket taker putter - where - taker = do - mpipe <- atomically $ tryTakeEnv cache - case mpipe of - Nothing -> maker - Just env -> isDead env >>= \b -> if not b then return env else killer env >> maker - - putter env = do - accepted <- atomically $ tryPutEnv cache env - unless accepted $ killer env - --- *** Limited --- | Takes an env and returns it on completion of the function. --- If all envs are already taken, this will wait. This should have a constant number of environments --- --- @since 0.3.6 -withEnvLimited :: Spawner env -> VCache env -> TSem -> (env -> IO a) -> IO a -withEnvLimited spawner vcache envsem = bracket taker putter - where - taker = limitMakeEnv spawner vcache envsem - putter env = atomically $ putEnv vcache env - -limitMakeEnv :: Spawner env -> VCache env -> TSem -> IO env -limitMakeEnv Spawner{..} vcache envsem = go - where - go = do - eenvpermission <- atomically $ ( Left <$> takeEnv vcache ) - `orElse` ( Right <$> waitTSem envsem ) - case eenvpermission of - Right () -> maker - Left env -> do - -- Given our env, we check if it's dead. If it's not, we are done and return it. - -- If it is dead, we release it, signal that a new env can be created, and then recurse - isdead <- isDead env - if not isdead then return env - else do - killer env - atomically $ signalTSem envsem - go - --- * Low level -initializeEmptyCache :: Int -> IO (VCache env) -initializeEmptyCache n | n < 1 = return mempty - | otherwise = Vector.replicateM n newEmptyTMVarIO - -takeEnv :: VCache env -> STM env -takeEnv = Vector.foldl folding retry - where folding m stmenv = m `orElse` takeTMVar stmenv - -tryTakeEnv :: VCache env -> STM (Maybe env) -tryTakeEnv cache = (Just <$> takeEnv cache) `orElse` pure Nothing - -putEnv :: VCache env -> env -> STM () -putEnv cache env = Vector.foldl folding retry cache - where folding m stmenv = m `orElse` putTMVar stmenv env - -tryPutEnv :: VCache env -> env -> STM Bool -tryPutEnv cache env = (putEnv cache env *> return True) `orElse` pure False - -releaseCache :: Cache env -> IO () -releaseCache cache = Vector.mapM_ qkRelease (vcache cache) - where qkRelease tenv = atomically (tryTakeTMVar tenv) - >>= maybe (return ()) (killer $ spawner cache) diff --git a/testsuite/tests/concurrent/should_run/all.T b/testsuite/tests/concurrent/should_run/all.T index abac22a..69b8ad7 100644 --- a/testsuite/tests/concurrent/should_run/all.T +++ b/testsuite/tests/concurrent/should_run/all.T @@ -284,4 +284,3 @@ test('hs_try_putmvar003', # Check forkIO exception determinism under optimization test('T13330', normal, compile_and_run, ['-O']) -test('T13916', normal, compile_and_run, ['-O2']) From git at git.haskell.org Thu Jul 20 16:50:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 16:50:04 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump haddock submodule (4f81642) Message-ID: <20170720165004.CB3793A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/4f816422f3c06c0860e24290242f8f8c664975c5/ghc >--------------------------------------------------------------- commit 4f816422f3c06c0860e24290242f8f8c664975c5 Author: Ben Gamari Date: Thu Jul 20 08:43:01 2017 -0400 Bump haddock submodule >--------------------------------------------------------------- 4f816422f3c06c0860e24290242f8f8c664975c5 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 22cbf4d..cc1577a 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 22cbf4d9509d3b537e6c2fcf4c95ae73d930b9aa +Subproject commit cc1577ae29763dfeb9483b5c7dcc723bb3a014f0 From git at git.haskell.org Thu Jul 20 16:50:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 16:50:13 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: rts: Claim AP_STACK before adjusting Sp (ffea6cf) Message-ID: <20170720165013.0A87E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/ffea6cfe7137093c32cd2357fb9fdf9db9430543/ghc >--------------------------------------------------------------- commit ffea6cfe7137093c32cd2357fb9fdf9db9430543 Author: Ben Gamari Date: Thu Jul 20 11:33:51 2017 -0400 rts: Claim AP_STACK before adjusting Sp In the fix to #13615 we introduced some logic to atomically blackhole AP_STACKs closures upon entry. However, this logic was placed *after* a stack pointer adjustment. This meant that if someone else beat us to blackholing the AP_STACK we would suspend the thread with uninitialized content on the stack. This would then later blow up when threadPaused attempted to walk the stack, hence #13970. Silly bug but still cost lots of head-scratching to find. Thanks to albertov for the great repro. Fixes #13970. Bug originally introduced by the fix to #13615. Reviewers: austin, erikd, simonmar Reviewed By: erikd, simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13970, #13615 Differential Revision: https://phabricator.haskell.org/D3760 (cherry picked from commit bade356f79d44c9f6e8918a89d9ffac7f5608dbf) >--------------------------------------------------------------- ffea6cfe7137093c32cd2357fb9fdf9db9430543 rts/Apply.cmm | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/rts/Apply.cmm b/rts/Apply.cmm index ceeddde..fafcc7a 100644 --- a/rts/Apply.cmm +++ b/rts/Apply.cmm @@ -637,11 +637,6 @@ INFO_TABLE(stg_AP_STACK,/*special layout*/0,0,AP_STACK,"AP_STACK","AP_STACK") * than continuing to evaluate the now-defunct closure. */ STK_CHK_ENTER(WDS(Words) + SIZEOF_StgUpdateFrame + WDS(AP_STACK_SPLIM), R1); - /* ensure there is at least AP_STACK_SPLIM words of headroom available - * after unpacking the AP_STACK. See bug #1466 */ - - PUSH_UPD_FRAME(Sp - SIZEOF_StgUpdateFrame, R1); - Sp = Sp - SIZEOF_StgUpdateFrame - WDS(Words); /* * It is imperative that we blackhole lest we may duplicate computation which @@ -657,6 +652,11 @@ INFO_TABLE(stg_AP_STACK,/*special layout*/0,0,AP_STACK,"AP_STACK","AP_STACK") prim_write_barrier; SET_INFO(ap, __stg_EAGER_BLACKHOLE_info); + /* ensure there is at least AP_STACK_SPLIM words of headroom available + * after unpacking the AP_STACK. See bug #1466 */ + PUSH_UPD_FRAME(Sp - SIZEOF_StgUpdateFrame, R1); + Sp = Sp - SIZEOF_StgUpdateFrame - WDS(Words); + TICK_ENT_AP(); LDV_ENTER(ap); ENTER_CCS_THUNK(ap); From git at git.haskell.org Thu Jul 20 16:50:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 16:50:10 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: distrib/configure: Canonicalize triples (e86ebd4) Message-ID: <20170720165010.4E44A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/e86ebd4f35a3d55db8855a31fa8c9bd6971dcafc/ghc >--------------------------------------------------------------- commit e86ebd4f35a3d55db8855a31fa8c9bd6971dcafc Author: Ben Gamari Date: Thu Jul 20 11:34:00 2017 -0400 distrib/configure: Canonicalize triples Previously we failed to do this, which meant that the bindist's configure would fail when passed --target (as you may need to do when installing an armv7 bindist on an aarch64 machine, for instance). Reviewers: hvr, erikd, austin Reviewed By: hvr Subscribers: rwbarton, thomie GHC Trac Issues: #13934 Differential Revision: https://phabricator.haskell.org/D3761 (cherry picked from commit 1480080b31e9f7cd47ca7b677455b3558b0da2bc) >--------------------------------------------------------------- e86ebd4f35a3d55db8855a31fa8c9bd6971dcafc distrib/configure.ac.in | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index 3d2d90d..27ae965 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -13,6 +13,13 @@ dnl-------------------------------------------------------------------- FP_GMP bootstrap_target=@TargetPlatform@ + +# We have to run these unconditionally as FPTOOLS_SET_PLATFORM_VARS wants the +# values it computes. +AC_CANONICAL_BUILD +AC_CANONICAL_HOST +AC_CANONICAL_TARGET + FPTOOLS_SET_PLATFORM_VARS # Requires FPTOOLS_SET_PLATFORM_VARS to be run first. From git at git.haskell.org Thu Jul 20 16:50:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 16:50:07 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: ghc-prim: Bump version (8c5405f) Message-ID: <20170720165007.93FE63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/8c5405f63c2de0c445ec171aab63c35786544b9e/ghc >--------------------------------------------------------------- commit 8c5405f63c2de0c445ec171aab63c35786544b9e Author: Ben Gamari Date: Thu Jul 20 11:27:45 2017 -0400 ghc-prim: Bump version >--------------------------------------------------------------- 8c5405f63c2de0c445ec171aab63c35786544b9e libraries/ghc-compact/ghc-compact.cabal | 2 +- libraries/ghc-prim/ghc-prim.cabal | 2 +- testsuite/tests/ado/ado004.stderr | 2 +- testsuite/tests/backpack/should_compile/bkp16.stderr | 2 +- testsuite/tests/determinism/determ021/determ021.stdout | 4 ++-- testsuite/tests/driver/json2.stderr | 4 ++-- testsuite/tests/indexed-types/should_compile/T3017.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ADT.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr1.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr2.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr3.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr4.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr5.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr6.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/BoolToBool.stderr | 2 +- .../tests/partial-sigs/should_compile/DataFamilyInstanceLHS.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Defaulting1MROn.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Defaulting2MROff.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Defaulting2MROn.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Either.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/EqualityConstraint.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Every.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/EveryNamed.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ExpressionSig.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ExpressionSigNamed.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ExtraConstraints1.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ExtraConstraints2.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ExtraConstraints3.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROff.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROn.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Forall1.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/GenNamed.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/HigherRank1.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/HigherRank2.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/LocalDefinitionBug.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Meltdown.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/MonoLocalBinds.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/NamedTyVar.stderr | 2 +- .../should_compile/NamedWildcardInDataFamilyInstanceLHS.stderr | 2 +- .../should_compile/NamedWildcardInTypeFamilyInstanceLHS.stderr | 2 +- .../tests/partial-sigs/should_compile/ParensAroundContext.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/PatBind.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/PatBind2.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/PatternSig.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Recursive.stderr | 2 +- .../tests/partial-sigs/should_compile/ScopedNamedWildcards.stderr | 2 +- .../tests/partial-sigs/should_compile/ScopedNamedWildcardsGood.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ShowNamed.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/SimpleGen.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/SkipMany.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/SomethingShowable.stderr | 2 +- .../tests/partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Uncurry.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/UncurryNamed.stderr | 2 +- .../partial-sigs/should_compile/WarningWildcardInstantiations.stderr | 2 +- testsuite/tests/roles/should_compile/Roles1.stderr | 2 +- testsuite/tests/roles/should_compile/Roles14.stderr | 2 +- testsuite/tests/roles/should_compile/Roles2.stderr | 2 +- testsuite/tests/roles/should_compile/Roles3.stderr | 2 +- testsuite/tests/roles/should_compile/Roles4.stderr | 2 +- testsuite/tests/roles/should_compile/T8958.stderr | 2 +- testsuite/tests/typecheck/should_compile/T12763.stderr | 2 +- testsuite/tests/typecheck/should_compile/tc231.stderr | 2 +- 63 files changed, 65 insertions(+), 65 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 8c5405f63c2de0c445ec171aab63c35786544b9e From git at git.haskell.org Thu Jul 20 16:50:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 16:50:16 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Make IfaceAxiom typechecking lazier. (31c5c7c) Message-ID: <20170720165016.E242C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/31c5c7c5ba8587d6e06782c260db1b3313a05df6/ghc >--------------------------------------------------------------- commit 31c5c7c5ba8587d6e06782c260db1b3313a05df6 Author: Edward Z. Yang Date: Thu Jul 20 11:30:46 2017 -0400 Make IfaceAxiom typechecking lazier. Fixes #13803, but adds a note about a yet to be fixed #13981. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #13803 Differential Revision: https://phabricator.haskell.org/D3742 (cherry picked from commit fdb6a5bfd545094782fb539951b561ac2467443d) >--------------------------------------------------------------- 31c5c7c5ba8587d6e06782c260db1b3313a05df6 compiler/iface/TcIface.hs | 9 ++- compiler/typecheck/FamInst.hs | 69 ++++++++++++++++++---- testsuite/tests/driver/T13803/D.hs | 5 ++ testsuite/tests/driver/T13803/E.hs | 11 ++++ testsuite/tests/driver/T13803/E.hs-boot | 1 + .../tests/{cabal/pkg02 => driver/T13803}/Makefile | 2 + testsuite/tests/driver/T13803/T13803.stdout | 5 ++ testsuite/tests/driver/T13803/Y.hs | 6 ++ testsuite/tests/driver/T13803/Y.hs-boot | 3 + testsuite/tests/driver/T13803/all.T | 4 ++ 10 files changed, 103 insertions(+), 12 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 31c5c7c5ba8587d6e06782c260db1b3313a05df6 From git at git.haskell.org Thu Jul 20 18:03:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 18:03:53 +0000 (UTC) Subject: [commit: packages/process] tag 'v1.6.1.0' created Message-ID: <20170720180353.CE5463A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process New tag : v1.6.1.0 Referencing: 25eb632265671b35c019a2af6e5c1180d3279b58 From git at git.haskell.org Thu Jul 20 18:03:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 18:03:55 +0000 (UTC) Subject: [commit: packages/process] master: Export withCreateProcess documentation (13db296) Message-ID: <20170720180355.D4C473A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/13db29626502a43854c4cdaaa0526ea19e03c525/process >--------------------------------------------------------------- commit 13db29626502a43854c4cdaaa0526ea19e03c525 Author: Jonathan Lange Date: Mon May 22 16:37:35 2017 +0100 Export withCreateProcess documentation The function is public, but the Haddock documentation isn't being rendered. I think it's a simple matter of removing the `{-` and `-}`, but I haven't tested locally. >--------------------------------------------------------------- 13db29626502a43854c4cdaaa0526ea19e03c525 System/Process.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/System/Process.hs b/System/Process.hs index 8842daa..7c1a342 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -199,7 +199,6 @@ createProcess cp = do | hdl /= stdin && hdl /= stdout && hdl /= stderr = hClose hdl maybeCloseStd _ = return () -{- -- | A 'C.bracket'-style resource handler for 'createProcess'. -- -- Does automatic cleanup when the action finishes. If there is an exception @@ -214,7 +213,6 @@ createProcess cp = do -- > ... -- -- @since 1.4.3.0 --} withCreateProcess :: CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a) From git at git.haskell.org Thu Jul 20 18:03:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 18:03:59 +0000 (UTC) Subject: [commit: packages/process] master: gitignore cabal sandbox and new-build files (d5bb035) Message-ID: <20170720180359.E252F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d5bb0351374437d34721f691d50649a7db3cdebf/process >--------------------------------------------------------------- commit d5bb0351374437d34721f691d50649a7db3cdebf Author: George Wilson Date: Thu Jun 22 13:32:35 2017 +1000 gitignore cabal sandbox and new-build files >--------------------------------------------------------------- d5bb0351374437d34721f691d50649a7db3cdebf .gitignore | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/.gitignore b/.gitignore index a123a67..44073d0 100644 --- a/.gitignore +++ b/.gitignore @@ -1,4 +1,8 @@ +/.cabal-sandbox/ +/cabal.project.local +/cabal.sandbox.config /dist/ +/dist-newstyle/ /.stack-work/ *.swp From git at git.haskell.org Thu Jul 20 18:03:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 18:03:57 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #97 from jml/patch-1 (807c467) Message-ID: <20170720180357.DBFFD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/807c467f5baa85df496c23d0c26f4427af8593f8/process >--------------------------------------------------------------- commit 807c467f5baa85df496c23d0c26f4427af8593f8 Merge: 88547b0 13db296 Author: Michael Snoyman Date: Wed May 24 08:28:58 2017 -0600 Merge pull request #97 from jml/patch-1 Export withCreateProcess documentation >--------------------------------------------------------------- 807c467f5baa85df496c23d0c26f4427af8593f8 System/Process.hs | 2 -- 1 file changed, 2 deletions(-) From git at git.haskell.org Thu Jul 20 18:04:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 18:04:01 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #98 from gwils/more-gitignore (e3ff9b7) Message-ID: <20170720180401.E90A03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e3ff9b70eb5c410a7bb2d82876fac98f13bf9b78/process >--------------------------------------------------------------- commit e3ff9b70eb5c410a7bb2d82876fac98f13bf9b78 Merge: 807c467 d5bb035 Author: Michael Snoyman Date: Thu Jun 22 06:55:22 2017 +0300 Merge pull request #98 from gwils/more-gitignore gitignore cabal sandbox and new-build files >--------------------------------------------------------------- e3ff9b70eb5c410a7bb2d82876fac98f13bf9b78 .gitignore | 4 ++++ 1 file changed, 4 insertions(+) From git at git.haskell.org Thu Jul 20 18:04:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 18:04:03 +0000 (UTC) Subject: [commit: packages/process] master: Version bump for v1.6.1.0 (fixes #99) (423a9ef) Message-ID: <20170720180403.EF5473A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/423a9efa8b1b22304af0acc8b950289026b288eb/process >--------------------------------------------------------------- commit 423a9efa8b1b22304af0acc8b950289026b288eb Author: Michael Snoyman Date: Thu Jul 20 18:56:17 2017 +0300 Version bump for v1.6.1.0 (fixes #99) >--------------------------------------------------------------- 423a9efa8b1b22304af0acc8b950289026b288eb changelog.md | 2 +- process.cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/changelog.md b/changelog.md index 537a744..9e94142 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,6 @@ # Changelog for [`process` package](http://hackage.haskell.org/package/process) -## Unreleased changes +## 1.6.1.1 *July 2017* * Expose `CGid`, `GroupID`, and `UserID` from `System.Process.Internals` [#90](https://github.com/haskell/process/issues/90) diff --git a/process.cabal b/process.cabal index 98516f6..1415c2f 100644 --- a/process.cabal +++ b/process.cabal @@ -1,5 +1,5 @@ name: process -version: 1.6.0.0 +version: 1.6.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE From git at git.haskell.org Thu Jul 20 18:04:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 18:04:06 +0000 (UTC) Subject: [commit: packages/process] master: Add "Unreleased changes" section (1f2795a) Message-ID: <20170720180406.01FD53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1f2795ae255356075579a137c30702f0a3762937/process >--------------------------------------------------------------- commit 1f2795ae255356075579a137c30702f0a3762937 Author: Michael Snoyman Date: Thu Jul 20 18:58:39 2017 +0300 Add "Unreleased changes" section >--------------------------------------------------------------- 1f2795ae255356075579a137c30702f0a3762937 changelog.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/changelog.md b/changelog.md index 9e94142..c7a946f 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,7 @@ # Changelog for [`process` package](http://hackage.haskell.org/package/process) +## Unreleased changes + ## 1.6.1.1 *July 2017* * Expose `CGid`, `GroupID`, and `UserID` from `System.Process.Internals` From git at git.haskell.org Thu Jul 20 19:23:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 19:23:54 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump process submodule to 1.6.1.0 (15dfb33) Message-ID: <20170720192354.92C663A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/15dfb33aab66e4d09958eacb58241478311baf26/ghc >--------------------------------------------------------------- commit 15dfb33aab66e4d09958eacb58241478311baf26 Author: Ben Gamari Date: Thu Jul 20 12:54:00 2017 -0400 Bump process submodule to 1.6.1.0 >--------------------------------------------------------------- 15dfb33aab66e4d09958eacb58241478311baf26 libraries/process | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/process b/libraries/process index 88547b0..423a9ef 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit 88547b0fae8644f8f69be32c7ee5a3b76051c82f +Subproject commit 423a9efa8b1b22304af0acc8b950289026b288eb From git at git.haskell.org Thu Jul 20 20:54:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 20:54:05 +0000 (UTC) Subject: [commit: packages/parsec] master: Make lib:parsec -Wall clean (e193de0) Message-ID: <20170720205405.9D0303A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/parsec On branch : master Link : http://git.haskell.org/packages/parsec.git/commitdiff/e193de020f5ec317a4ae230330b7bf390fd39d7e >--------------------------------------------------------------- commit e193de020f5ec317a4ae230330b7bf390fd39d7e Author: Herbert Valerio Riedel Date: Tue Jul 18 23:55:29 2017 +0200 Make lib:parsec -Wall clean >--------------------------------------------------------------- e193de020f5ec317a4ae230330b7bf390fd39d7e Text/Parsec/Char.hs | 4 ++- Text/Parsec/Combinator.hs | 14 ++++----- Text/Parsec/Error.hs | 2 +- Text/Parsec/Expr.hs | 4 +-- Text/Parsec/Perm.hs | 3 +- Text/Parsec/Prim.hs | 24 +++++++++------- Text/Parsec/Text.hs | 1 - Text/Parsec/Text/Lazy.hs | 1 - Text/Parsec/Token.hs | 54 ++++++++++++++++++----------------- Text/ParserCombinators/Parsec/Expr.hs | 1 - parsec.cabal | 1 + 11 files changed, 58 insertions(+), 51 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 e193de020f5ec317a4ae230330b7bf390fd39d7e From git at git.haskell.org Thu Jul 20 20:54:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 20:54:07 +0000 (UTC) Subject: [commit: packages/parsec] master: M-x delete-trailing-whitespace (b6c2d8e) Message-ID: <20170720205407.A29A93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/parsec On branch : master Link : http://git.haskell.org/packages/parsec.git/commitdiff/b6c2d8e30b254acf053c3e9a340a9b0eab7216f0 >--------------------------------------------------------------- commit b6c2d8e30b254acf053c3e9a340a9b0eab7216f0 Author: Herbert Valerio Riedel Date: Tue Jul 18 23:59:01 2017 +0200 M-x delete-trailing-whitespace >--------------------------------------------------------------- b6c2d8e30b254acf053c3e9a340a9b0eab7216f0 Text/Parsec/ByteString.hs | 0 Text/Parsec/Char.hs | 0 Text/Parsec/Combinator.hs | 0 Text/Parsec/Error.hs | 0 Text/Parsec/Expr.hs | 0 Text/Parsec/Perm.hs | 0 Text/Parsec/Pos.hs | 0 Text/Parsec/Prim.hs | 0 Text/Parsec/String.hs | 0 Text/Parsec/Text.hs | 0 Text/Parsec/Text/Lazy.hs | 0 Text/Parsec/Token.hs | 0 Text/ParserCombinators/Parsec/Char.hs | 0 Text/ParserCombinators/Parsec/Combinator.hs | 0 Text/ParserCombinators/Parsec/Error.hs | 0 Text/ParserCombinators/Parsec/Expr.hs | 0 Text/ParserCombinators/Parsec/Language.hs | 0 Text/ParserCombinators/Parsec/Perm.hs | 0 Text/ParserCombinators/Parsec/Pos.hs | 0 Text/ParserCombinators/Parsec/Prim.hs | 0 Text/ParserCombinators/Parsec/Token.hs | 0 21 files changed, 0 insertions(+), 0 deletions(-) From git at git.haskell.org Thu Jul 20 23:24:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Jul 2017 23:24:28 +0000 (UTC) Subject: [commit: ghc] master: HsPat: Assume that no spliced patterns are irrefutable (36e8bcb) Message-ID: <20170720232428.9A9A43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/36e8bcba08446dbc4e7532ef9db5517c13977bf9/ghc >--------------------------------------------------------------- commit 36e8bcba08446dbc4e7532ef9db5517c13977bf9 Author: Ben Gamari Date: Thu Jul 20 19:24:00 2017 -0400 HsPat: Assume that no spliced patterns are irrefutable This is a conservative assumption which will limit some uses of spliced patterns, but it fixes #13984. Test Plan: Validate Reviewers: RyanGlScott, AaronFriel, austin Reviewed By: RyanGlScott Subscribers: rwbarton, thomie GHC Trac Issues: #13984 Differential Revision: https://phabricator.haskell.org/D3766 >--------------------------------------------------------------- 36e8bcba08446dbc4e7532ef9db5517c13977bf9 compiler/hsSyn/HsPat.hs | 16 +++++++--------- testsuite/tests/typecheck/should_compile/T13984.hs | 9 +++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 17 insertions(+), 9 deletions(-) diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs index 93ad9ec..f7d1876 100644 --- a/compiler/hsSyn/HsPat.hs +++ b/compiler/hsSyn/HsPat.hs @@ -620,7 +620,7 @@ isIrrefutableHsPat pat go1 (SigPatOut pat _) = go pat go1 (TuplePat pats _ _) = all go pats go1 (SumPat pat _ _ _) = go pat - go1 (ListPat {}) = False + go1 (ListPat {}) = False go1 (PArrPat {}) = False -- ? go1 (ConPatIn {}) = False -- Conservative @@ -632,15 +632,13 @@ isIrrefutableHsPat pat go1 (ConPatOut{ pat_con = L _ (PatSynCon _pat) }) = False -- Conservative - go1 (LitPat {}) = False - go1 (NPat {}) = False - go1 (NPlusKPat {}) = False + go1 (LitPat {}) = False + go1 (NPat {}) = False + go1 (NPlusKPat {}) = False - -- Both should be gotten rid of by renamer before - -- isIrrefutablePat is called - go1 (SplicePat {}) = urk pat - - urk pat = pprPanic "isIrrefutableHsPat:" (ppr pat) + -- We conservatively assume that no TH splices are irrefutable + -- since we cannot know until the splice is evaluated. + go1 (SplicePat {}) = False hsPatNeedsParens :: Pat a -> Bool hsPatNeedsParens (NPlusKPat {}) = True diff --git a/testsuite/tests/typecheck/should_compile/T13984.hs b/testsuite/tests/typecheck/should_compile/T13984.hs new file mode 100644 index 0000000..a17e48c --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13984.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE TemplateHaskell #-} +module Panic where + +import Language.Haskell.TH + +expr :: IO Exp +expr = runQ $ do + name <- newName "foo" + [| do $(varP name) <- pure (); pure () |] diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index ee37b9a..2ce4e91 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -570,3 +570,4 @@ test('T13879', normal, compile, ['']) test('T13881', normal, compile, ['']) test('T13915a', normal, multimod_compile, ['T13915a', '-v0']) test('T13915b', normal, compile, ['']) +test('T13984', normal, compile, ['']) From git at git.haskell.org Fri Jul 21 00:35:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Jul 2017 00:35:56 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: ONLY_PERF_TESTS=YES now fully implemented (09ac10e) Message-ID: <20170721003556.3EB513A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/09ac10e6630f9d812d7046667c291721fe5843e3/ghc >--------------------------------------------------------------- commit 09ac10e6630f9d812d7046667c291721fe5843e3 Author: Jared Weakly Date: Wed Jul 12 17:30:31 2017 -0700 ONLY_PERF_TESTS=YES now fully implemented >--------------------------------------------------------------- 09ac10e6630f9d812d7046667c291721fe5843e3 testsuite/driver/runtests.py | 2 ++ testsuite/driver/testlib.py | 1 + 2 files changed, 3 insertions(+) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index c09b063..996dae1 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -337,6 +337,8 @@ else: sys.stdout.flush() summary(t, sys.stdout, config.no_print_summary) + print("Only perf tests: " + str(config.only_perf_tests) + "\n") + print("Skip perf tests: " + str(config.skip_perf_tests) + "\n") if config.summary_file != '': with open(config.summary_file, 'w') as file: diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index ae82d1f..a54fe38 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -714,6 +714,7 @@ def test_common_work(watcher, name, opts, func, args): and (getTestOpts().only_ways == None or way in getTestOpts().only_ways) \ and (config.cmdline_ways == [] or way in config.cmdline_ways) \ and (not (config.skip_perf_tests and isStatsTest())) \ + and (not (config.only_perf_tests and (not isStatsTest()))) \ and way not in getTestOpts().omit_ways # Which ways we are asked to skip From git at git.haskell.org Fri Jul 21 00:35:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Jul 2017 00:35:58 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Added initial metric comparison tooling (415a990) Message-ID: <20170721003558.EEE073A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/415a990c6651ba5d5aaeac29a90b7e77aa9feac6/ghc >--------------------------------------------------------------- commit 415a990c6651ba5d5aaeac29a90b7e77aa9feac6 Author: Jared Weakly Date: Thu Jul 20 17:30:21 2017 -0700 Added initial metric comparison tooling >--------------------------------------------------------------- 415a990c6651ba5d5aaeac29a90b7e77aa9feac6 testsuite/driver/runtests.py | 9 +++------ testsuite/driver/testutil.py | 10 ++++++---- 2 files changed, 9 insertions(+), 10 deletions(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index e0c652a..d9e98d4 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -338,14 +338,11 @@ else: summary(t, sys.stdout, config.no_print_summary) - # This here is loading up all of the git notes into memory. - # It's most likely in the wrong spot and I haven't fully fleshed out - # where exactly I'm putting this and how I'm refactoring the performance - # test running logic. - # Currently this is useful for debugging, at least. + # Write our accumulated metrics into the git notes for this commit. if config.use_git_notes: note = subprocess.check_output(["git","notes","--ref=perf","append","-m", "\n".join(config.accumulate_metrics)]) - parse_git_notes('perf') # Should this be hardcoded? Most likely not... + # v-- This is in a nonsensical area. It should be happening before all of the tests are even run. + # parse_git_notes('perf') # Should it even be happening in the test-driver logic anymore? if config.summary_file != '': with open(config.summary_file, 'w') as file: diff --git a/testsuite/driver/testutil.py b/testsuite/driver/testutil.py index 1fe1c20..bf9ed2a 100644 --- a/testsuite/driver/testutil.py +++ b/testsuite/driver/testutil.py @@ -3,7 +3,6 @@ import os import platform import subprocess import shutil - import threading def strip_quotes(s): @@ -50,14 +49,17 @@ def lndir(srcdir, dstdir): # This function allows one to read in git notes from the commandline # and then breaks it into a list of dictionaries that can be parsed # later on in the testing functions. -def parse_git_notes(namespace): +# I wanted to put it in perf_notes.py but couldn't figure out a nice way to do that. +def parse_git_notes(namespace, commits=['HEAD']): logFields = ['TEST_ENV','TEST','WAY','METRIC','VALUE'] - log = subprocess.check_output(['git', 'notes', '--ref=' + namespace, 'show']).decode('utf-8') + log = "" + for commit in commits: + log += subprocess.check_output(['git', 'notes', '--ref=' + namespace, 'show', commit]).decode('utf-8') + log = log.strip('\n').split('\n') log = [line.strip('\t').split('\t') for line in log] log = [dict(zip(logFields, field)) for field in log] return log - # Add a print statement here if you want to see what's being loaded from git notes. # On Windows, os.symlink is not defined with Python 2.7, but is in Python 3 # when using msys2, as GHC does. Unfortunately, only Administrative users have From git at git.haskell.org Fri Jul 21 00:36:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Jul 2017 00:36:01 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Can now load up git note data into python (67b0ccf) Message-ID: <20170721003601.AFE543A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/67b0ccfcebc6cf2b0ef75c5010dfaaa8ac4f6d40/ghc >--------------------------------------------------------------- commit 67b0ccfcebc6cf2b0ef75c5010dfaaa8ac4f6d40 Author: Jared Weakly Date: Tue Jul 18 12:17:57 2017 -0700 Can now load up git note data into python >--------------------------------------------------------------- 67b0ccfcebc6cf2b0ef75c5010dfaaa8ac4f6d40 testsuite/driver/runtests.py | 6 ++++-- testsuite/driver/testutil.py | 12 +++++++++--- 2 files changed, 13 insertions(+), 5 deletions(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index 996dae1..239003c 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -337,8 +337,10 @@ else: sys.stdout.flush() summary(t, sys.stdout, config.no_print_summary) - print("Only perf tests: " + str(config.only_perf_tests) + "\n") - print("Skip perf tests: " + str(config.skip_perf_tests) + "\n") + + if config.use_git_notes: + note = subprocess.check_output(["git","notes","--ref=perf","append","-m", "\n".join(config.accumulate_metrics)]) + parse_git_notes('perf') # Should this be hardcoded? Most likely not... if config.summary_file != '': with open(config.summary_file, 'w') as file: diff --git a/testsuite/driver/testutil.py b/testsuite/driver/testutil.py index c6297ff..59906a0 100644 --- a/testsuite/driver/testutil.py +++ b/testsuite/driver/testutil.py @@ -47,9 +47,15 @@ def lndir(srcdir, dstdir): os.mkdir(dst) lndir(src, dst) -# def git_append(note): -# def print_metrics(): -# print(config.accumulate_metrics) +# This function allows one to read in git notes from the commandline +# and then breaks it into a list of dictionaries that can be parsed +# later on in the testing functions. +def parse_git_notes(namespace): + logFields = ['TEST_ENV','TEST','WAY','METRIC','VALUE'] + log = subprocess.check_output(['git', 'notes', '--ref=' + namespace, 'show']).decode('utf-8') + log = log.strip('\n').split('\n') + log = [entry.strip('\t').split('\t') for entry in log] + log = [dict(zip(logFields, row)) for row in log] # On Windows, os.symlink is not defined with Python 2.7, but is in Python 3 # when using msys2, as GHC does. Unfortunately, only Administrative users have From git at git.haskell.org Fri Jul 21 00:36:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Jul 2017 00:36:04 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Small changes to address Ben's comments (aebacee) Message-ID: <20170721003604.6DFFB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/aebaceecead47ae40be00de0ad6a8c530429cf42/ghc >--------------------------------------------------------------- commit aebaceecead47ae40be00de0ad6a8c530429cf42 Author: Jared Weakly Date: Tue Jul 18 17:35:34 2017 -0700 Small changes to address Ben's comments Signed-off-by: Jared Weakly >--------------------------------------------------------------- aebaceecead47ae40be00de0ad6a8c530429cf42 testsuite/driver/runtests.py | 13 +++++++++---- testsuite/driver/testglobals.py | 2 +- testsuite/driver/testlib.py | 5 ++--- testsuite/driver/testutil.py | 6 ++++-- 4 files changed, 16 insertions(+), 10 deletions(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index 239003c..e0c652a 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -54,9 +54,9 @@ long_options = [ "check-files-written", # check files aren't written by multiple tests "verbose=", # verbose (0,1,2 so far) "skip-perf-tests", # skip performance tests - "only-perf-tests", # Only do performance tests + "only-perf-tests", # Only do performance tests "use-git-notes", # use git notes to store metrics. NOTE: This is expected to become the default and will eventually be taken out. - "TEST_ENV=", # Override default chosen test-env. + "test-env=", # Override default chosen test-env. ] opts, args = getopt.getopt(sys.argv[1:], "e:", long_options) @@ -125,8 +125,8 @@ for opt,arg in opts: sys.exit(1) config.verbose = int(arg) - if opt == '--TEST_ENV': - config.TEST_ENV = arg + if opt == '--test-env': + config.test_env = arg config.cygwin = False @@ -338,6 +338,11 @@ else: summary(t, sys.stdout, config.no_print_summary) + # This here is loading up all of the git notes into memory. + # It's most likely in the wrong spot and I haven't fully fleshed out + # where exactly I'm putting this and how I'm refactoring the performance + # test running logic. + # Currently this is useful for debugging, at least. if config.use_git_notes: note = subprocess.check_output(["git","notes","--ref=perf","append","-m", "\n".join(config.accumulate_metrics)]) parse_git_notes('perf') # Should this be hardcoded? Most likely not... diff --git a/testsuite/driver/testglobals.py b/testsuite/driver/testglobals.py index bd8eefe..aa81b32 100644 --- a/testsuite/driver/testglobals.py +++ b/testsuite/driver/testglobals.py @@ -125,7 +125,7 @@ class TestConfig: # To accumulate the metrics for the git notes self.accumulate_metrics = [] # Has the user defined a custom test environment? Local is default. - self.TEST_ENV = 'local' + self.test_env = 'local' global config config = TestConfig() diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index a54fe38..a5a97fa 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1085,7 +1085,6 @@ def stats( name, way, stats_file ): # Check -t stats info def checkStats(name, way, stats_file, range_fields): - full_name = name + '(' + way + ')' result = passed() @@ -1111,8 +1110,8 @@ def checkStats(name, way, stats_file, range_fields): # Add val into the git note if option is set. if config.use_git_notes: - test_env = config.TEST_ENV - config.accumulate_metrics.append(test_env + '\t' + name + '\t' + way + '\t' + field + '\t' + str(val)) + test_env = config.test_env + config.accumulate_metrics.append('\t'.join([test_env, name, way, field, str(val)])) if val < lowerBound: print(field, 'value is too low:') diff --git a/testsuite/driver/testutil.py b/testsuite/driver/testutil.py index 59906a0..1fe1c20 100644 --- a/testsuite/driver/testutil.py +++ b/testsuite/driver/testutil.py @@ -54,8 +54,10 @@ def parse_git_notes(namespace): logFields = ['TEST_ENV','TEST','WAY','METRIC','VALUE'] log = subprocess.check_output(['git', 'notes', '--ref=' + namespace, 'show']).decode('utf-8') log = log.strip('\n').split('\n') - log = [entry.strip('\t').split('\t') for entry in log] - log = [dict(zip(logFields, row)) for row in log] + log = [line.strip('\t').split('\t') for line in log] + log = [dict(zip(logFields, field)) for field in log] + return log + # Add a print statement here if you want to see what's being loaded from git notes. # On Windows, os.symlink is not defined with Python 2.7, but is in Python 3 # when using msys2, as GHC does. Unfortunately, only Administrative users have From git at git.haskell.org Fri Jul 21 00:36:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Jul 2017 00:36:10 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Weird merging issues. Hopefully I didn't break things horrifically (5f4a7f0) Message-ID: <20170721003610.138E63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/5f4a7f0fb2ce8f4289145c093d95fd719778cd2a/ghc >--------------------------------------------------------------- commit 5f4a7f0fb2ce8f4289145c093d95fd719778cd2a Merge: 415a990 cd4e438 Author: Jared Weakly Date: Thu Jul 20 17:37:37 2017 -0700 Weird merging issues. Hopefully I didn't break things horrifically >--------------------------------------------------------------- 5f4a7f0fb2ce8f4289145c093d95fd719778cd2a utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Jul 21 00:36:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Jul 2017 00:36:07 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Basic metrics collection and command line options working (78e16f5) Message-ID: <20170721003607.309DA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/78e16f5946df1c17e176a82469b1a05a0e2ff7aa/ghc >--------------------------------------------------------------- commit 78e16f5946df1c17e176a82469b1a05a0e2ff7aa Author: Jared Weakly Date: Thu Jul 6 17:16:49 2017 -0700 Basic metrics collection and command line options working >--------------------------------------------------------------- 78e16f5946df1c17e176a82469b1a05a0e2ff7aa libraries/array | 2 +- libraries/hoopl | 1 + testsuite/driver/runtests.py | 36 ++++++++++++++++++++++++------------ testsuite/driver/testglobals.py | 11 ++++++++++- testsuite/driver/testlib.py | 6 ++++++ testsuite/driver/testutil.py | 4 ++++ testsuite/mk/test.mk | 12 ++++++++++++ 7 files changed, 58 insertions(+), 14 deletions(-) diff --git a/libraries/array b/libraries/array index 9a23fea..f7b69e9 160000 --- a/libraries/array +++ b/libraries/array @@ -1 +1 @@ -Subproject commit 9a23feac0b78e713c0f7877066fa24dbc2217c20 +Subproject commit f7b69e9cb914cb69bbede5264729523fb8669db1 diff --git a/libraries/hoopl b/libraries/hoopl new file mode 160000 index 0000000..ac24864 --- /dev/null +++ b/libraries/hoopl @@ -0,0 +1 @@ +Subproject commit ac24864c2db7951a6f34674e2b11b69d37ef84ff diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index 7e4f375..c09b063 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -42,18 +42,21 @@ def signal_handler(signal, frame): # cmd-line options long_options = [ - "configfile=", # config file - "config=", # config field - "rootdir=", # root of tree containing tests (default: .) - "summary-file=", # file in which to save the (human-readable) summary - "no-print-summary=", # should we print the summary? - "only=", # just this test (can be give multiple --only= flags) - "way=", # just this way - "skipway=", # skip this way - "threads=", # threads to run simultaneously - "check-files-written", # check files aren't written by multiple tests - "verbose=", # verbose (0,1,2 so far) - "skip-perf-tests", # skip performance tests + "configfile=", # config file + "config=", # config field + "rootdir=", # root of tree containing tests (default: .) + "summary-file=", # file in which to save the (human-readable) summary + "no-print-summary=", # should we print the summary? + "only=", # just this test (can be give multiple --only= flags) + "way=", # just this way + "skipway=", # skip this way + "threads=", # threads to run simultaneously + "check-files-written", # check files aren't written by multiple tests + "verbose=", # verbose (0,1,2 so far) + "skip-perf-tests", # skip performance tests + "only-perf-tests", # Only do performance tests + "use-git-notes", # use git notes to store metrics. NOTE: This is expected to become the default and will eventually be taken out. + "TEST_ENV=", # Override default chosen test-env. ] opts, args = getopt.getopt(sys.argv[1:], "e:", long_options) @@ -110,12 +113,21 @@ for opt,arg in opts: if opt == '--skip-perf-tests': config.skip_perf_tests = True + if opt == '--only-perf-tests': + config.only_perf_tests = True + + if opt == '--use-git-notes': + config.use_git_notes = True + if opt == '--verbose': if arg not in ["0","1","2","3","4","5"]: sys.stderr.write("ERROR: requested verbosity %s not supported, use 0,1,2,3,4 or 5" % arg) sys.exit(1) config.verbose = int(arg) + if opt == '--TEST_ENV': + config.TEST_ENV = arg + config.cygwin = False config.msys = False diff --git a/testsuite/driver/testglobals.py b/testsuite/driver/testglobals.py index fc050e6..bd8eefe 100644 --- a/testsuite/driver/testglobals.py +++ b/testsuite/driver/testglobals.py @@ -117,6 +117,16 @@ class TestConfig: # Should we skip performance tests self.skip_perf_tests = False + # Only do performance tests + self.only_perf_tests = False + + # Should we dump statistics to git notes? + self.use_git_notes = False + # To accumulate the metrics for the git notes + self.accumulate_metrics = [] + # Has the user defined a custom test environment? Local is default. + self.TEST_ENV = 'local' + global config config = TestConfig() @@ -283,4 +293,3 @@ default_testopts = TestOptions() # (bug, directory, name) of tests marked broken global brokens brokens = [] - diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 26e3d17..ae82d1f 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1084,6 +1084,7 @@ def stats( name, way, stats_file ): # Check -t stats info def checkStats(name, way, stats_file, range_fields): + full_name = name + '(' + way + ')' result = passed() @@ -1107,6 +1108,11 @@ def checkStats(name, way, stats_file, range_fields): deviation = round(((float(val) * 100)/ expected) - 100, 1) + # Add val into the git note if option is set. + if config.use_git_notes: + test_env = config.TEST_ENV + config.accumulate_metrics.append(test_env + '\t' + name + '\t' + way + '\t' + field + '\t' + str(val)) + if val < lowerBound: print(field, 'value is too low:') print('(If this is because you have improved GHC, please') diff --git a/testsuite/driver/testutil.py b/testsuite/driver/testutil.py index dcba177..c6297ff 100644 --- a/testsuite/driver/testutil.py +++ b/testsuite/driver/testutil.py @@ -47,6 +47,10 @@ def lndir(srcdir, dstdir): os.mkdir(dst) lndir(src, dst) +# def git_append(note): +# def print_metrics(): +# print(config.accumulate_metrics) + # On Windows, os.symlink is not defined with Python 2.7, but is in Python 3 # when using msys2, as GHC does. Unfortunately, only Administrative users have # the privileges necessary to create symbolic links by default. Consequently we diff --git a/testsuite/mk/test.mk b/testsuite/mk/test.mk index a44e200..9896883 100644 --- a/testsuite/mk/test.mk +++ b/testsuite/mk/test.mk @@ -195,6 +195,18 @@ ifeq "$(SKIP_PERF_TESTS)" "YES" RUNTEST_OPTS += --skip-perf-tests endif +ifeq "$(ONLY_PERF_TESTS)" "YES" +RUNTEST_OPTS += --only-perf-tests +endif + +ifeq "$(USE_GIT_NOTES)" "YES" +RUNTEST_OPTS += --use-git-notes +endif + +ifneq "$(TEST_ENV)" "" +RUNTEST_OPTS += --TEST_ENV="$(TEST_ENV)" +endif + ifeq "$(CLEANUP)" "0" RUNTEST_OPTS += -e config.cleanup=False else ifeq "$(CLEANUP)" "NO" From git at git.haskell.org Fri Jul 21 00:36:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Jul 2017 00:36:12 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite's head updated: Weird merging issues. Hopefully I didn't break things horrifically (5f4a7f0) Message-ID: <20170721003612.AEB193A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/perf-testsuite' now includes: bd4fdc6 Implement split-sections support for windows. c2303df aclocal.m4: allow arbitrary string in toolchain triplets e1146ed Fix typos in Bag.hs [ci skip] 81377e9 Big-obj support for the Windows runtime linker c506f83 Pretty-printer no longer butchers function arrow fixity 4f69013 testsuite: Decrease T13701 allocations 31ceaba user-guide: Various fixes to FFI section 905dc8b Make ':info Coercible' display an arbitrary string (fixes #12390) 7c9e356 Fix Work Balance computation in RTS stats b0c9f34 Improve Wmissing-home-modules warning under Cabal 6cff2ca Add testcase for T13818 15fcd9a Suppress unused warnings for selectors for some derived classes cb8db9b Sort list of failed tests for easier comparison between runs b8f33bc Always allow -staticlib fe6618b ByteCodeGen: use depth instead of offsets in BCEnv ccb849f users-guide/rel-notes: Describe #13875 fix 81de42c Add Template Haskell support for overloaded labels abda03b Optimize TimerManager ea75124 Fix logic error in GhcMake.enableCodeGenForTH ba46e63 Fix #13948 by being pickier about when to suggest DataKinds 85ac65c Fix #13947 by checking for unbounded names more ef7fd0a Parenthesize infix type names in data declarations in TH printer ec351b8 Add Template Haskell support for overloaded labels a249e93 Remove unnecessarily returned res_ty from rejigConRes d3bdd6c testsuite: Fix T13701 allocations yet again fcd2db1 configure: Ensure that we don't set LD to unusable linker be04c16 StgLint: Don't loop on tycons with runtime rep arguments 20880b5 testsuite: Show stderr output on command failure a0d9169 Fix minor typo 3a163aa Remove redundant import; fix note 4befb41 Mention which -Werror promoted a warning to an error 9b9f978 Use correct section types syntax for architecture 1ee49cb Fix missing escape in macro 60ec8f7 distrib/configure: Fail if we can't detect machine's word size 7ae4a28 [iserv] Fixing the word size for RemotePtr and toWordArray 5743581 testsuite: Update haddock allocations 4700baa testsuite: Again update allocations of T13701 1909985 Fix some excessive spacing in error messages f656fba [skip ci] Temporarily disable split-sections on Windows. 12ae1fa Fix a missing getNewNursery(), and related cleanup 935acb6 Typos in comments and explanation for unusused imports b8fec69 Make module membership on ModuleGraph faster 6ab3c5f Typeable: Always use UTF-8 string unpacking primitive d7b1751 configure: Cleanup ARM COPY bug test artifacts a051b55 testsuite: Ensure that hs_try_putmvar003 terminates c9e4c86 Allow visible type application for [] 1ed41a7 Fix links to SPJ’s papers (fixes #12578) 0b89b2d Add Haddocks for Eq (STRef a) and Eq (IORef a) c940e3b dmdAnal: Ensure that ExnStr flag isn't dropped inappropriately 6e3c901 Fix #13983 by creating a TyConFlavour type, and using it 927e781 typo: -XUndeci[d]ableInstances b066d93 base: Improve docs to clarify when finalizers may not be run cc839c5 Typeable: Ensure that promoted data family instance tycons get bindings a273c73 Spelling fixes eeb141d Demand: Improve comments 8e51bfc Introduce -fcatch-bottoms c9c762d testsuite: Pipe stdin directly to process a85a595 arcconfig: Set project ruleset to use master merge-base by default 194384f Fix busy-wait in SysTools.builderMainLoop fdb6a5b Make IfaceAxiom typechecking lazier. 5469ac8 Interpreter.c: use macros to access/modify Sp bade356 rts: Claim AP_STACK before adjusting Sp 1480080 distrib/configure: Canonicalize triples b2d3ec3 testsuite: Add test for #13916 ccac387 Revert "testsuite: Add test for #13916" 36e8bcb HsPat: Assume that no spliced patterns are irrefutable 78e16f5 Basic metrics collection and command line options working 09ac10e ONLY_PERF_TESTS=YES now fully implemented 67b0ccf Can now load up git note data into python aebacee Small changes to address Ben's comments 415a990 Added initial metric comparison tooling 5f4a7f0 Weird merging issues. Hopefully I didn't break things horrifically From git at git.haskell.org Fri Jul 21 00:41:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Jul 2017 00:41:38 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Initial tooling to compare across commits (but for actual this time) (43757d7) Message-ID: <20170721004138.D24683A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/43757d79bf1a8d16be3cda43dc23b894e78e6a84/ghc >--------------------------------------------------------------- commit 43757d79bf1a8d16be3cda43dc23b894e78e6a84 Author: Jared Weakly Date: Thu Jul 20 17:43:27 2017 -0700 Initial tooling to compare across commits (but for actual this time) >--------------------------------------------------------------- 43757d79bf1a8d16be3cda43dc23b894e78e6a84 testsuite/driver/perf_notes.py | 85 ++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 85 insertions(+) diff --git a/testsuite/driver/perf_notes.py b/testsuite/driver/perf_notes.py new file mode 100644 index 0000000..ea289fc --- /dev/null +++ b/testsuite/driver/perf_notes.py @@ -0,0 +1,85 @@ +#1/usr/bin/env python3 + +# +# (c) Jared Weakly 2017 +# +# This file will be a utility to help facilitate the comparison of performance +# metrics across arbitrary commits. The file will produce a table comparing +# metrics between measurements taken for given commits in the environment given +# by --test-env. +# +# The file will also (for now) exist as a library to import git-note +# functionality for the project into other files so everywhere has access to +# functions such as parse_git_notes. +# +# It will take a few arguments: +# --test-env= +# --test-name= (optional: If given, filters table to include only tests matching the given regular expression.) +# --min-delta= (optional: Display only tests where the relative spread is greater than the given value.) +# All following arguments will be the commits to compare. + +from __future__ import print_function + +# TODO: Actually figure out what imports I need. +import argparse +import re +import os +import string +import subprocess + +from testutil import parse_git_notes + +# --------- Comparison Utilities -------- # +parser = argparse.ArgumentParser() +parser.add_argument("--test-env", + help="The given test environment to be compared.") #, + # required=True) # Should I make this required? +parser.add_argument("--test-name", + help="Optional: If given, filters table to include only \ + tests matching the given regular expression.") +parser.add_argument("--min-delta", + help="Optional: Display only tests where the relative \ + spread is greater than the given value.") +parser.add_argument("commits", nargs=argparse.REMAINDER) + +args = parser.parse_args() + +# Defaults +env = 'local' +name = re.compile('.*') +metrics = [] + +# I should figure out a nice way to mark data with the commit it comes from +# so that I can display test performance numbers in order from oldest to newest commit. +if args.commits: + print(args.commits) + metrics = parse_git_notes('perf',args.commits) + +if args.test_env: + env = args.test_env + metrics = [test for test in metrics if test['TEST_ENV'] == env] + +if args.test_name: + name = re.compile(args.test_name) + metrics = [test for test in metrics if name.search(test.get('TEST',''))] + +# Logic should probably go here to sort, group, and otherwise prepare the list +# of dicts for being pretty printed. +print(metrics) + +# I'll redo this table almost entirely, it's just a proof of concept for now. +# Ideally the list of metrics should be grouped by same test and organized from oldest to newest commits +# and each test will have its own small paragraph. I'm envisioning something like: +# -------------------------------- +# Test Foo: test_env, test_way, metric +# --------------------------------- +# commit1 commit2 commit3 ... +# number1 number2 number3 ... +# +# Gosh, I want to just print a list of dictionaries pretty like but don't want to just add some random dependency... +# Table is hardcoded and pretty ugly, but... it works. +# For now, this table just pretty prints the list of dictionaries. +print("{:<12} {:<10} {:<10} {:<20} {:<15}".format('TEST_ENV','TEST','WAY','METRIC','VALUE')) +for key in metrics: + print("{:<12} {:<10} {:<10} {:<20} {:<15}" + .format(key['TEST_ENV'],key['TEST'],key['WAY'],key['METRIC'],key['VALUE'])) From git at git.haskell.org Fri Jul 21 02:16:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Jul 2017 02:16:15 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: HsPat: Assume that no spliced patterns are irrefutable (b45d127) Message-ID: <20170721021615.AEE9B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/b45d1277ada4b5ce30d5cfa188fb020f4806d9ea/ghc >--------------------------------------------------------------- commit b45d1277ada4b5ce30d5cfa188fb020f4806d9ea Author: Ben Gamari Date: Thu Jul 20 19:24:00 2017 -0400 HsPat: Assume that no spliced patterns are irrefutable This is a conservative assumption which will limit some uses of spliced patterns, but it fixes #13984. Test Plan: Validate Reviewers: RyanGlScott, AaronFriel, austin Reviewed By: RyanGlScott Subscribers: rwbarton, thomie GHC Trac Issues: #13984 Differential Revision: https://phabricator.haskell.org/D3766 (cherry picked from commit 36e8bcba08446dbc4e7532ef9db5517c13977bf9) >--------------------------------------------------------------- b45d1277ada4b5ce30d5cfa188fb020f4806d9ea compiler/hsSyn/HsPat.hs | 16 +++++++--------- testsuite/tests/typecheck/should_compile/T13984.hs | 9 +++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 17 insertions(+), 9 deletions(-) diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs index 174e837..23dbd75 100644 --- a/compiler/hsSyn/HsPat.hs +++ b/compiler/hsSyn/HsPat.hs @@ -617,7 +617,7 @@ isIrrefutableHsPat pat go1 (SigPatOut pat _) = go pat go1 (TuplePat pats _ _) = all go pats go1 (SumPat pat _ _ _) = go pat - go1 (ListPat {}) = False + go1 (ListPat {}) = False go1 (PArrPat {}) = False -- ? go1 (ConPatIn {}) = False -- Conservative @@ -629,15 +629,13 @@ isIrrefutableHsPat pat go1 (ConPatOut{ pat_con = L _ (PatSynCon _pat) }) = False -- Conservative - go1 (LitPat {}) = False - go1 (NPat {}) = False - go1 (NPlusKPat {}) = False + go1 (LitPat {}) = False + go1 (NPat {}) = False + go1 (NPlusKPat {}) = False - -- Both should be gotten rid of by renamer before - -- isIrrefutablePat is called - go1 (SplicePat {}) = urk pat - - urk pat = pprPanic "isIrrefutableHsPat:" (ppr pat) + -- We conservatively assume that no TH splices are irrefutable + -- since we cannot know until the splice is evaluated. + go1 (SplicePat {}) = False hsPatNeedsParens :: Pat a -> Bool hsPatNeedsParens (NPlusKPat {}) = True diff --git a/testsuite/tests/typecheck/should_compile/T13984.hs b/testsuite/tests/typecheck/should_compile/T13984.hs new file mode 100644 index 0000000..a17e48c --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13984.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE TemplateHaskell #-} +module Panic where + +import Language.Haskell.TH + +expr :: IO Exp +expr = runQ $ do + name <- newName "foo" + [| do $(varP name) <- pure (); pure () |] diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index c33f66f..badb814 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -560,3 +560,4 @@ test('T13879', normal, compile, ['']) test('T13881', normal, compile, ['']) test('T13915a', normal, multimod_compile, ['T13915a', '-v0']) test('T13915b', normal, compile, ['']) +test('T13984', normal, compile, ['']) From git at git.haskell.org Fri Jul 21 02:16:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Jul 2017 02:16:18 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: build system: Ensure there are no duplicate files in bindist list (96ce538) Message-ID: <20170721021618.64BCB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/96ce53866496b72a3eb34ee13a2a9c5392c29fcb/ghc >--------------------------------------------------------------- commit 96ce53866496b72a3eb34ee13a2a9c5392c29fcb Author: Ben Gamari Date: Thu Jul 20 21:39:27 2017 -0400 build system: Ensure there are no duplicate files in bindist list Several executables inexplicably appear twice in bindist.list, which ends up producing multiple tar file entries, consequently breaking BSD tar during extraction. I spent a fair amount of time trying to work out where these duplicates were coming from to no avail. Since Hadrian is right around the corner I'm satisfied with a terrible hack: just uniq bindist.list before producing the bindist tarball. Test Plan: Validate Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #13979, #13974 Differential Revision: https://phabricator.haskell.org/D3767 (cherry picked from commit fefcbfa86b73517d5002366d0703ce694c6d228d) >--------------------------------------------------------------- 96ce53866496b72a3eb34ee13a2a9c5392c29fcb ghc.mk | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/ghc.mk b/ghc.mk index 0466164..5b9cf22 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1107,7 +1107,8 @@ unix-binary-dist-prep: $(call removeFiles,$(BIN_DIST_PREP_TAR)) # h means "follow symlinks", e.g. if aclocal.m4 is a symlink to a source # tree then we want to include the real file, not a symlink to it - cd bindistprep && "$(TAR_CMD)" hcf - -T ../bindist-list | $(TAR_COMP_CMD) -c > ../$(BIN_DIST_PREP_TAR_COMP) + sort bindist-list | uniq > bindist-list.uniq + cd bindistprep && "$(TAR_CMD)" hcf - -T ../bindist-list.uniq | $(TAR_COMP_CMD) -c > ../$(BIN_DIST_PREP_TAR_COMP) windows-binary-dist-prep: $(call removeTrees,bindistprep/) @@ -1418,6 +1419,7 @@ distclean : clean # We make these when making or testing bindists $(call removeFiles,bindist-list) + $(call removeFiles,bindist-list.uniq) $(call removeTrees,bindisttest/a) # Not sure why this is being cleaned here. From git at git.haskell.org Fri Jul 21 02:16:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Jul 2017 02:16:21 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: relnotes: More updates (f4014d1) Message-ID: <20170721021621.1B1313A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/f4014d19319129d95fefdc2bc636062a6b175585/ghc >--------------------------------------------------------------- commit f4014d19319129d95fefdc2bc636062a6b175585 Author: Ben Gamari Date: Thu Jul 20 21:48:01 2017 -0400 relnotes: More updates >--------------------------------------------------------------- f4014d19319129d95fefdc2bc636062a6b175585 docs/users_guide/8.2.1-notes.rst | 17 ++++++++++++----- 1 file changed, 12 insertions(+), 5 deletions(-) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index 2f8642e..540d22c 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -10,7 +10,7 @@ performance improvements over the 8.0 branch. Highlights ---------- -The highlights since the 8.0 release are: +The highlights since the 8.0 release include: - A new, more expressive ``Typeable`` mechanism @@ -26,6 +26,8 @@ The highlights since the 8.0 release are: - Compact regions support, allowing efficient garbage collection of large heaps +- More reliable DWARF debug information + Full details ------------ @@ -427,7 +429,7 @@ network. ghc-prim ~~~~~~~~ -- Version number 0.5.0.0 (was 0.3.1.0) +- Version number 0.5.1.0 (was 0.3.1.0) - Added new ``isByteArrayPinned#`` and ``isMutableByteArrayPinned#`` operation. @@ -452,12 +454,12 @@ integer-gmp process ~~~~~~~ -- Version number 1.6.0.0 (was 1.4.3.0) +- Version number 1.6.1.0 (was 1.4.3.0) template-haskell ~~~~~~~~~~~~~~~~ -- Version 2.12.0.0 XXXXX (was 2.11.1.0) +- Version 2.12.0.0 (was 2.11.1.0) - Added support for unboxed sums :ghc-ticket:`12478`. @@ -476,10 +478,15 @@ unix Win32 ~~~~~ -- Version number 2.3.1.1 (was 2.3.1.1) +- Version number 2.5.4.1 (was 2.3.1.1) Known bugs ---------- - At least one known program regresses in compile time significantly over 8.0. See :ghc-ticket:`13535`. + +- Some uses of type applications may cause GHC to panic. See :ghc-ticket:`13819`. + +- The compiler may loop during typechecking on some modules using + :ghc-flag:`-XUndecidableInstances`. See :ghc-ticket:`13943`. From git at git.haskell.org Fri Jul 21 02:16:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Jul 2017 02:16:26 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: typo: -XUndeci[d]ableInstances (c913205) Message-ID: <20170721021626.8E8B63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/c913205c45fbb46c09a1495fd782f0ae2b6534fc/ghc >--------------------------------------------------------------- commit c913205c45fbb46c09a1495fd782f0ae2b6534fc Author: Chris Martin Date: Sat Jul 15 19:23:50 2017 -0500 typo: -XUndeci[d]ableInstances (cherry picked from commit 927e7810f7dcea295c1f8e93535835e52da0edbb) >--------------------------------------------------------------- c913205c45fbb46c09a1495fd782f0ae2b6534fc 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 c116a5e..3dc64af 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -6982,7 +6982,7 @@ However see :ref:`ghci-decls` for the overlap rules in GHCi. Decidability of type synonym instances ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -.. ghc-flag:: -XUndeciableInstances +.. ghc-flag:: -XUndecidableInstances Relax restrictions on the decidability of type synonym family instances. From git at git.haskell.org Fri Jul 21 02:16:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Jul 2017 02:16:23 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: base: Improve docs to clarify when finalizers may not be run (2f96543) Message-ID: <20170721021623.C75D63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/2f9654329a5389b441d513abfd18a9e7c13b5770/ghc >--------------------------------------------------------------- commit 2f9654329a5389b441d513abfd18a9e7c13b5770 Author: Andrew Martin Date: Thu Jul 13 11:09:34 2017 -0400 base: Improve docs to clarify when finalizers may not be run (cherry picked from commit b066d936a919f6943de1acdc358d9e014b2cc663) >--------------------------------------------------------------- 2f9654329a5389b441d513abfd18a9e7c13b5770 libraries/base/System/Mem/Weak.hs | 26 ++++++++++++++++++++++++++ 1 file changed, 26 insertions(+) diff --git a/libraries/base/System/Mem/Weak.hs b/libraries/base/System/Mem/Weak.hs index b9580b5..3a00696 100644 --- a/libraries/base/System/Mem/Weak.hs +++ b/libraries/base/System/Mem/Weak.hs @@ -67,6 +67,10 @@ module System.Mem.Weak ( -- * A precise semantics -- $precise + + -- * Implementation notes + + -- $notes ) where import GHC.Weak @@ -140,3 +144,25 @@ A heap object is /reachable/ if: * It is the value or finalizer of a weak pointer object whose key is reachable. -} +{- $notes + +A finalizer is not always called after its weak pointer\'s object becomes +unreachable. There are two situations that can cause this: + + * If the object becomes unreachable right before the program exits, + then GC may not be performed. Finalizers run during GC, so finalizers + associated with the object do not run if GC does not happen. + + * If a finalizer throws an exception, subsequent finalizers that had + been queued to run after it do not get run. This behavior may change + in a future release. See issue + on the issue tracker. Writing a finalizer that throws exceptions is + discouraged. + +Other than these two caveats, users can always expect that a finalizer +will be run after its weak pointer\'s object becomes unreachable. However, +the second caveat means that users need to trust that all of their +transitive dependencies do not throw exceptions in finalizers, since +any finalizers can end up queued together. + +-} From git at git.haskell.org Fri Jul 21 02:17:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Jul 2017 02:17:08 +0000 (UTC) Subject: [commit: ghc] master: build system: Ensure there are no duplicate files in bindist list (fefcbfa) Message-ID: <20170721021708.A77423A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fefcbfa86b73517d5002366d0703ce694c6d228d/ghc >--------------------------------------------------------------- commit fefcbfa86b73517d5002366d0703ce694c6d228d Author: Ben Gamari Date: Thu Jul 20 21:39:27 2017 -0400 build system: Ensure there are no duplicate files in bindist list Several executables inexplicably appear twice in bindist.list, which ends up producing multiple tar file entries, consequently breaking BSD tar during extraction. I spent a fair amount of time trying to work out where these duplicates were coming from to no avail. Since Hadrian is right around the corner I'm satisfied with a terrible hack: just uniq bindist.list before producing the bindist tarball. Test Plan: Validate Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #13979, #13974 Differential Revision: https://phabricator.haskell.org/D3767 >--------------------------------------------------------------- fefcbfa86b73517d5002366d0703ce694c6d228d ghc.mk | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/ghc.mk b/ghc.mk index cdab331..4eb1658 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1125,7 +1125,8 @@ unix-binary-dist-prep: $(call removeFiles,$(BIN_DIST_PREP_TAR)) # h means "follow symlinks", e.g. if aclocal.m4 is a symlink to a source # tree then we want to include the real file, not a symlink to it - cd bindistprep && "$(TAR_CMD)" hcf - -T ../bindist-list | $(TAR_COMP_CMD) -c > ../$(BIN_DIST_PREP_TAR_COMP) + sort bindist-list | uniq > bindist-list.uniq + cd bindistprep && "$(TAR_CMD)" hcf - -T ../bindist-list.uniq | $(TAR_COMP_CMD) -c > ../$(BIN_DIST_PREP_TAR_COMP) windows-binary-dist-prep: $(call removeTrees,bindistprep/) @@ -1436,6 +1437,7 @@ distclean : clean # We make these when making or testing bindists $(call removeFiles,bindist-list) + $(call removeFiles,bindist-list.uniq) $(call removeTrees,bindisttest/a) # Not sure why this is being cleaned here. From git at git.haskell.org Fri Jul 21 21:14:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Jul 2017 21:14:56 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump Cabal submodule to 2.0.0.2 (3f88393) Message-ID: <20170721211456.5DC333A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/3f88393057fe5e4ad302b22e559649c81c576e69/ghc >--------------------------------------------------------------- commit 3f88393057fe5e4ad302b22e559649c81c576e69 Author: Ben Gamari Date: Fri Jul 21 14:56:05 2017 -0400 Bump Cabal submodule to 2.0.0.2 >--------------------------------------------------------------- 3f88393057fe5e4ad302b22e559649c81c576e69 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index 3aa2d69..082cf20 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 3aa2d69f12409ac675d5415dd1c3ef2db8e1b9e6 +Subproject commit 082cf2066b7206d3b12a9f92d832236e2484b4c1 From git at git.haskell.org Sat Jul 22 03:11:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Jul 2017 03:11:11 +0000 (UTC) Subject: [commit: ghc] master: Fix ungrammatical error message (acbbb50) Message-ID: <20170722031111.36B703A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/acbbb502014a2e0d08fec533990474876f746b89/ghc >--------------------------------------------------------------- commit acbbb502014a2e0d08fec533990474876f746b89 Author: Ryan Scott Date: Fri Jul 21 23:08:24 2017 -0400 Fix ungrammatical error message Test Plan: If it builds, ship it Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3772 >--------------------------------------------------------------- acbbb502014a2e0d08fec533990474876f746b89 compiler/rename/RnSource.hs | 2 +- .../tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.stderr | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs index ff7251e..244f46b 100644 --- a/compiler/rename/RnSource.hs +++ b/compiler/rename/RnSource.hs @@ -964,7 +964,7 @@ rnSrcDerivDecl (DerivDecl ty deriv_strat overlap) ; unless standalone_deriv_ok (addErr standaloneDerivErr) ; failIfTc (isJust deriv_strat && not deriv_strats_ok) $ illegalDerivStrategyErr $ fmap unLoc deriv_strat - ; (ty', fvs) <- rnLHsInstType (text "In a deriving declaration") ty + ; (ty', fvs) <- rnLHsInstType (text "a deriving declaration") ty ; return (DerivDecl ty' deriv_strat overlap, fvs) } standaloneDerivErr :: SDoc diff --git a/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.stderr b/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.stderr index 19df37a..8e98910 100644 --- a/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.stderr +++ b/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.stderr @@ -3,4 +3,4 @@ WildcardInStandaloneDeriving.hs:4:19: error: Malformed instance: _ WildcardInStandaloneDeriving.hs:4:19: error: Wildcard ‘_’ not allowed - in In a deriving declaration + in a deriving declaration From git at git.haskell.org Sat Jul 22 13:24:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Jul 2017 13:24:46 +0000 (UTC) Subject: [commit: ghc] master: fix dllwrap issue. (cbbf083) Message-ID: <20170722132446.B78923A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cbbf0837d47622f1a3e889a59690d96e7947c6cd/ghc >--------------------------------------------------------------- commit cbbf0837d47622f1a3e889a59690d96e7947c6cd Author: Tamar Christina Date: Sat Jul 22 14:11:07 2017 +0100 fix dllwrap issue. Summary: Always set dllwrap and windres values. Reviewers: austin, hvr, bgamari, trofi Reviewed By: trofi Subscribers: rwbarton, thomie, erikd GHC Trac Issues: #13792 Differential Revision: https://phabricator.haskell.org/D3775 >--------------------------------------------------------------- cbbf0837d47622f1a3e889a59690d96e7947c6cd configure.ac | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/configure.ac b/configure.ac index 043dea8..00fae0a 100644 --- a/configure.ac +++ b/configure.ac @@ -420,13 +420,13 @@ then AC_PATH_PROG([OBJDUMP],[objdump]) AC_PATH_PROG([DllWrap],[dllwrap]) AC_PATH_PROG([Windres],[windres]) +fi - DllWrapCmd="$DllWrap" - WindresCmd="$Windres" +DllWrapCmd="$DllWrap" +WindresCmd="$Windres" - AC_SUBST([DllWrapCmd]) - AC_SUBST([WindresCmd]) -fi +AC_SUBST([DllWrapCmd]) +AC_SUBST([WindresCmd]) FP_ICONV FP_GMP From git at git.haskell.org Sat Jul 22 14:20:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Jul 2017 14:20:22 +0000 (UTC) Subject: [commit: ghc] master: Avoid linear lookup in unload_wkr in the Linker (c1d9690) Message-ID: <20170722142022.A423C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c1d9690619ea38bad3b9aa529d72d10c6206f2e9/ghc >--------------------------------------------------------------- commit c1d9690619ea38bad3b9aa529d72d10c6206f2e9 Author: Bartosz Nitka Date: Fri Jul 21 11:41:41 2017 -0700 Avoid linear lookup in unload_wkr in the Linker I've encountered an issue with following reproduction steps: * `:load` a large number of modules (~2000) * compile a BCO that depends on many other BCOs from many other modules * `:reload` * try to compile anything, even `1` works Before this patch the last step takes ~5s. It takes 80ms after. Test Plan: harbormaster Reviewers: simonmar, austin, hvr, bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3770 >--------------------------------------------------------------- c1d9690619ea38bad3b9aa529d72d10c6206f2e9 compiler/ghci/Linker.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/ghci/Linker.hs b/compiler/ghci/Linker.hs index f326590..aee7684 100644 --- a/compiler/ghci/Linker.hs +++ b/compiler/ghci/Linker.hs @@ -1091,13 +1091,13 @@ unload_wkr hsc_env keep_linkables pls = do filter (not . null . linkableObjs) bcos_to_unload))) $ purgeLookupSymbolCache hsc_env - let bcos_retained = map linkableModule remaining_bcos_loaded + let bcos_retained = mkModuleSet $ map linkableModule remaining_bcos_loaded -- Note that we want to remove all *local* -- (i.e. non-isExternal) names too (these are the -- temporary bindings from the command line). keep_name (n,_) = isExternalName n && - nameModule n `elem` bcos_retained + nameModule n `elemModuleSet` bcos_retained itbl_env' = filterNameEnv keep_name (itbl_env pls) closure_env' = filterNameEnv keep_name (closure_env pls) From git at git.haskell.org Sat Jul 22 21:20:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Jul 2017 21:20:50 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump integer-gmp version (09396ec) Message-ID: <20170722212050.2758C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/09396ec3bb672e761c3e627484dd02c5a3a76c77/ghc >--------------------------------------------------------------- commit 09396ec3bb672e761c3e627484dd02c5a3a76c77 Author: Ben Gamari Date: Fri Jul 21 17:31:03 2017 -0400 Bump integer-gmp version >--------------------------------------------------------------- 09396ec3bb672e761c3e627484dd02c5a3a76c77 libraries/integer-gmp/changelog.md | 6 +++++- libraries/integer-gmp/integer-gmp.cabal | 2 +- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/libraries/integer-gmp/changelog.md b/libraries/integer-gmp/changelog.md index 3100349..b817881 100644 --- a/libraries/integer-gmp/changelog.md +++ b/libraries/integer-gmp/changelog.md @@ -1,11 +1,15 @@ # Changelog for [`integer-gmp` package](http://hackage.haskell.org/package/integer-gmp) -## 1.0.0.2 *July 2017* +## 1.0.1.0 *July 2017* * Bundled with GHC 8.2.1 * Optimize `minusInteger` + * Fix the right-shift operation for negative big integers (fixes GHC #12136) + + * Make operations more strict + ## 1.0.0.1 *Feb 2016* * Bundled with GHC 8.0.1 diff --git a/libraries/integer-gmp/integer-gmp.cabal b/libraries/integer-gmp/integer-gmp.cabal index 377efb3..2f32b34 100644 --- a/libraries/integer-gmp/integer-gmp.cabal +++ b/libraries/integer-gmp/integer-gmp.cabal @@ -1,5 +1,5 @@ name: integer-gmp -version: 1.0.0.1 +version: 1.0.1.0 synopsis: Integer library based on GMP license: BSD3 license-file: LICENSE From git at git.haskell.org Sat Jul 22 21:20:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Jul 2017 21:20:53 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Update autoconf scripts (b9b286c) Message-ID: <20170722212053.03BE83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/b9b286c034613d350d8a83af645dd64f5d49c962/ghc >--------------------------------------------------------------- commit b9b286c034613d350d8a83af645dd64f5d49c962 Author: Ben Gamari Date: Fri Jul 21 17:58:22 2017 -0400 Update autoconf scripts Scripts taken from autoconf 81497f5aaf50a12a9fe0cba30ef18bda46b62959 >--------------------------------------------------------------- b9b286c034613d350d8a83af645dd64f5d49c962 config.guess | 197 +++++++++++++++++++++++-------------- config.sub | 90 ++++++++++++----- libraries/base/config.guess | 197 +++++++++++++++++++++++-------------- libraries/base/config.sub | 90 ++++++++++++----- libraries/integer-gmp/config.guess | 197 +++++++++++++++++++++++-------------- libraries/integer-gmp/config.sub | 90 ++++++++++++----- 6 files changed, 573 insertions(+), 288 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 b9b286c034613d350d8a83af645dd64f5d49c962 From git at git.haskell.org Sat Jul 22 21:20:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Jul 2017 21:20:55 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: relnotes: Address split sections and linker changes (78ef8f2) Message-ID: <20170722212055.B36CA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/78ef8f2fc495545c49d222abccbe337dd41cabbb/ghc >--------------------------------------------------------------- commit 78ef8f2fc495545c49d222abccbe337dd41cabbb Author: Ben Gamari Date: Fri Jul 21 18:10:06 2017 -0400 relnotes: Address split sections and linker changes Thanks to @duog for mentioning that this wasn't covered. >--------------------------------------------------------------- 78ef8f2fc495545c49d222abccbe337dd41cabbb docs/users_guide/8.2.1-notes.rst | 31 +++++++++++++++++++++++-------- 1 file changed, 23 insertions(+), 8 deletions(-) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index 540d22c..fdd7d48 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -45,6 +45,29 @@ Language Compiler ~~~~~~~~ +- GHC will now use ``ld.gold`` or ``ld.lld`` instead of the system's default + ``ld``, if available. Linker availability will be evaluated at ``configure`` + time. The user can manually override which linker to use by passing the ``LD`` + variable to ``configure``. You can revert to the old behavior of using the + system's default ``ld`` by passing the ``--disable-ld-override`` flag to + ``configure``. + +- GHC now uses section splitting (i.e. :ghc-flag:`-split-sections`) instead of + object splitting (i.e. :ghc-flag:`-split-objs`) as the default mechanism for + linker-based dead code removal. While the effect is the same, split sections + tends to produce significantly smaller objects than split objects and more + closely mirrors the approach used by other compilers. Split objects will + be deprecated and eventually removed in a future GHC release. + + Note that some versions of the ubiquitous BFD linker exhibit performance + trouble with large libraries with section splitting enabled (see + :ghc-ticket:`13739`). It is recommended that you use either the ``gold`` or + ``lld`` linker if you observe this. This will require that you install one of + these compilers, rerun ``configure``, and reinstall GHC. + + Split sections is enabled by default in the official binary distributions for + platforms that support it. + - Old profiling flags ``-auto-all``, ``-auto``, and ``-caf-all`` are deprecated and their usage provokes a compile-time warning. @@ -317,14 +340,6 @@ Runtime system - advapi32, shell32 and user32 are now automatically loaded in GHCi. libGCC is also loaded when a depencency requires it. See :ghc-ticket:`13189`. -Build system -~~~~~~~~~~~~ - -- GHC will now use ``ld.gold`` or ``ld.lld`` instead of the system's default - ``ld``, if available. Linker availability will be evaluated at ``configure`` - time. The user can manually override which linker to use by passing the ``LD`` - variable to ``configure``. - hsc2hs ~~~~~~ From git at git.haskell.org Sat Jul 22 21:21:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Jul 2017 21:21:03 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: aclocal.m4: allow arbitrary string in toolchain triplets (afec638) Message-ID: <20170722212103.D959D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/afec638e93b77c183c6e9dd4b5fe7d4d2ba41fb6/ghc >--------------------------------------------------------------- commit afec638e93b77c183c6e9dd4b5fe7d4d2ba41fb6 Author: Sergei Trofimovich Date: Sat Jul 8 09:47:12 2017 +0100 aclocal.m4: allow arbitrary string in toolchain triplets Canonical triplets have a form of --[-] Checking for vendor is almost never correct as it's an arbitrary string. It's useful to have multiple "vendors" to denote otherwise the same (WRT , , ) target: --target=x86_64-pc-linux-gnu --target=x86_64-unknown-linux-gnu --target=x86_64-ghc80-linux-gnu --target=x86_64-ghchead-linux-gnu Do not fail unknown vendors. Only emit a warning. Ideally configure checks should never use "vendor". Signed-off-by: Sergei Trofimovich (cherry picked from commit c2303dff95aa174021a1950656fdf9a1cf983959) >--------------------------------------------------------------- afec638e93b77c183c6e9dd4b5fe7d4d2ba41fb6 aclocal.m4 | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 79067eb..fe2c43d 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -231,8 +231,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS], dec|none|unknown|hp|apple|next|sun|sgi|ibm|montavista|portbld) ;; *) - echo "Unknown vendor [$]1" - exit 1 + AC_MSG_WARN([Unknown vendor [$]1]) ;; esac } From git at git.haskell.org Sat Jul 22 21:21:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Jul 2017 21:21:06 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix label type for __stginit_* labels: those are .data labels, not .text (119ca4c) Message-ID: <20170722212106.90C773A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/119ca4c97f7e7ab952420645d3f907008b8468ec/ghc >--------------------------------------------------------------- commit 119ca4c97f7e7ab952420645d3f907008b8468ec Author: Sergei Trofimovich Date: Sat Jul 22 10:49:12 2017 +0100 Fix label type for __stginit_* labels: those are .data labels, not .text Noticed when was building --enable-unregisterised build for x86_64: ``` /tmp/ghc22931_0/ghc_3.hc:5:9: error: error: '__stginit_ghczmprim_GHCziTypes' redeclared as different kind of symbol StgWord __stginit_ghczmprim_GHCziTypes[]__attribute__((aligned(8)))= { ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ | 5 | StgWord __stginit_ghczmprim_GHCziTypes[]__attribute__((aligned(8)))= { | ^ In file included from /tmp/ghc22931_0/ghc_3.hc:3:0: error: /tmp/ghc22931_0/ghc_3.hc:4:5: error: note: previous declaration of '__stginit_ghczmprim_GHCziTypes' was here EF_(__stginit_ghczmprim_GHCziTypes); ^ ``` The error here is mismatch in symbol type: EF_ ("external function") It should be EC_ ("external closure"). The same build failure does not happen in HEAD because the __stginit_* is not generated there anymore (see a92ff5d66182d992d02dfaad4c446ad074582368) Fixes #14009 Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 119ca4c97f7e7ab952420645d3f907008b8468ec compiler/cmm/CLabel.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs index 5f13bed..89b5e9a 100644 --- a/compiler/cmm/CLabel.hs +++ b/compiler/cmm/CLabel.hs @@ -930,7 +930,7 @@ labelType (RtsLabel (RtsApInfoTable _ _)) = DataLabel labelType (RtsLabel (RtsApFast _)) = CodeLabel labelType (CaseLabel _ CaseReturnInfo) = DataLabel labelType (CaseLabel _ _) = CodeLabel -labelType (PlainModuleInitLabel _) = CodeLabel +labelType (PlainModuleInitLabel _) = DataLabel labelType (SRTLabel _) = DataLabel labelType (LargeSRTLabel _) = DataLabel labelType (LargeBitmapLabel _) = DataLabel From git at git.haskell.org Sat Jul 22 21:21:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Jul 2017 21:21:01 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: relnotes: Fix wibbles (11a5cc0) Message-ID: <20170722212101.2746E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/11a5cc0911f9bbce372b38940f345a0c8bd2006a/ghc >--------------------------------------------------------------- commit 11a5cc0911f9bbce372b38940f345a0c8bd2006a Author: Ben Gamari Date: Fri Jul 21 18:39:22 2017 -0400 relnotes: Fix wibbles >--------------------------------------------------------------- 11a5cc0911f9bbce372b38940f345a0c8bd2006a docs/users_guide/8.2.1-notes.rst | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index fdd7d48..2aef7d4 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -12,7 +12,7 @@ Highlights The highlights since the 8.0 release include: -- A new, more expressive ``Typeable`` mechanism +- A new, more expressive ``Typeable`` mechanism, ``Type.Reflection`` - Colorful error messages with caret diagnostics @@ -88,7 +88,7 @@ Compiler been completely overhauled. The instance context is now inferred using the type signatures (and default type signatures) of the derived class's methods instead of using the datatype's definition, which often led to - overconstrained instances or instances that didn't typecheck (or worse, + over-constrained instances or instances that didn't typecheck (or worse, triggered GHC panics). See the section on :ref:`DeriveAnyClass ` for more details. @@ -167,7 +167,7 @@ Compiler on feedback from tooling authors for the next release. - GHC is now able to better optimize polymorphic expressions by using known - superclass dictionaries where possible. Some examples: + superclass dictionaries where possible. Some examples: :: -- uses of `Monad IO` or `Applicative IO` here are improved foo :: MonadBaseControl IO m => ... @@ -186,12 +186,12 @@ Compiler - GHC now ignores ``RULES`` for data constructors (:ghc-ticket:`13290`). Previously, it accepted:: - "NotAllowed" forall x. Just x = e + {-# RULES "NotAllowed" forall x. Just x = e #-} That rule will no longer take effect, and a warning will be issued. ``RULES`` may still mention data constructors, but not in the outermost position:: - "StillWorks" forall x. f (Just x) = e + {-# RULES "StillWorks" forall x. f (Just x) = e #-} - Type synonyms can no longer appear in the class position of an instance. This means something like this is no longer allowed: :: @@ -299,9 +299,9 @@ Runtime system - Heap overflow throws a catchable exception, provided that it was detected by the RTS during a GC cycle due to the program exceeding a limit set by - ``+RTS -M``, and not due to an allocation being refused by the operating - system. This exception is thrown to the same thread that receives - ``UserInterrupt`` exceptions, and may be caught by user programs. + ``+RTS -M`` (see :rts-flag:`-M`), and not due to an allocation being refused + by the operating system. This exception is thrown to the same thread that + receives ``UserInterrupt`` exceptions, and may be caught by user programs. - Added support for *Compact Regions*, which offer a way to manually move long-lived data outside of the heap so that the garbage From git at git.haskell.org Sat Jul 22 21:20:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Jul 2017 21:20:58 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Release 8.2.1 (0cee252) Message-ID: <20170722212058.6D4F73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/0cee25253f9f2cb4f19f021fd974bdad3c26a80b/ghc >--------------------------------------------------------------- commit 0cee25253f9f2cb4f19f021fd974bdad3c26a80b Author: Ben Gamari Date: Fri Jul 21 17:28:19 2017 -0400 Release 8.2.1 >--------------------------------------------------------------- 0cee25253f9f2cb4f19f021fd974bdad3c26a80b ANNOUNCE | 55 ++++++++++++++++++++++++++++--------------------------- configure.ac | 4 ++-- 2 files changed, 30 insertions(+), 29 deletions(-) diff --git a/ANNOUNCE b/ANNOUNCE index c00db3c..b1ce086 100644 --- a/ANNOUNCE +++ b/ANNOUNCE @@ -1,53 +1,54 @@ =============================================== - The Glasgow Haskell Compiler -- version 8.0.1 + The Glasgow Haskell Compiler -- version 8.2.1 =============================================== -The GHC Team is pleased to announce a new super-major release of GHC. This is -the most significant GHC release in quite some time, including both a number -of major features and numerous bug fixes. These include, +The GHC Team is pleased to announce a new major release of GHC. The themes of this +release have been performance, stability, and consolidation. Consequently +cleanups can be seen throughout the compiler, - * The TypeInType extension, which unifies types and kinds, allowing GHC - to reason about kind equality and enabling promotion of GADTs to the type - level. + * Significant improvements in compiler performance - * Support for record pattern synonyms + * More robust support for levity polymorphism - * The -XDeriveAnyClass extension learned to derive instances for classes with - associated types + * Reliable DWARF debugging information - * More reliable DWARF debugging information + * Improved runtime system performance on NUMA systems - * Support for injective type families + * Retooling of the cost-center profiler, including support for live streaming + of profile data via the GHC event log - * Applicative do-notation + * Deterministic interface files - * Support for wildcards in data and type family instances + * More robust treatment of join points, enabling significantly better code + generation in many cases - * Strict and StrictData extensions, allowing modules to be compiled with - strict-by-default bindings + * Numerous improvements in robustness on Windows - * The DuplicateRecordFields extensions, allowing multiple datatypes to declare - the same record field names provided they are used unambiguously + * Resolution of over 500 tickets - * Support for implicit parameters providing light-weight callstacks and source - locations +In addition, there are a number of new features, - * User-defined error messages for type errors + * A new more type-safe Typeable mechanism - * A rewritten (and greatly improved) pattern exhaustiveness checker + * The long-awaited Backpack module system - * GHCi can run the interpreter in a separate process, and the interpreter can - now run profiled code + * Deriving strategies to disambiguate between GHC's various instance deriving + mechanisms - * A native code generator for powerpc64 and powerpc64le architectures + * Unboxed sums types, for efficient unpacked representation of sum data types - * and more! + * Compact regions, allowing better control over garbage collection with in the + presence of large heaps containing many long-lived objects. + + * Colorful messages and caret diagnostics for more legible errors + + * Automatic support for using the faster gold and lld linkers when available A more thorough list of the changes in the release can be found in the release notes, - http://haskell.org/ghc/docs/8.0.1/html/users_guide/release-8-0-1.html + http://haskell.org/ghc/docs/8.2.1/html/users_guide/release-8-2-1.html How to get it diff --git a/configure.ac b/configure.ac index bad688a..f8bdd49 100644 --- a/configure.ac +++ b/configure.ac @@ -13,10 +13,10 @@ dnl # see what flags are available. (Better yet, read the documentation!) # -AC_INIT([The Glorious Glasgow Haskell Compilation System], [8.2.0], [glasgow-haskell-bugs at haskell.org], [ghc-AC_PACKAGE_VERSION]) +AC_INIT([The Glorious Glasgow Haskell Compilation System], [8.2.1], [glasgow-haskell-bugs at haskell.org], [ghc-AC_PACKAGE_VERSION]) # Set this to YES for a released version, otherwise NO -: ${RELEASE=NO} +: ${RELEASE=YES} # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line # above. If this is not a released version, then we will append the From git at git.haskell.org Sat Jul 22 21:52:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Jul 2017 21:52:26 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Set RELEASE=NO (2716e43) Message-ID: <20170722215226.9C4163A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/2716e43cfd083c30b981d360e7a662061984ebaf/ghc >--------------------------------------------------------------- commit 2716e43cfd083c30b981d360e7a662061984ebaf Author: Ben Gamari Date: Sat Jul 22 17:52:08 2017 -0400 Set RELEASE=NO >--------------------------------------------------------------- 2716e43cfd083c30b981d360e7a662061984ebaf configure.ac | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/configure.ac b/configure.ac index f8bdd49..6d217a1 100644 --- a/configure.ac +++ b/configure.ac @@ -16,7 +16,7 @@ dnl AC_INIT([The Glorious Glasgow Haskell Compilation System], [8.2.1], [glasgow-haskell-bugs at haskell.org], [ghc-AC_PACKAGE_VERSION]) # Set this to YES for a released version, otherwise NO -: ${RELEASE=YES} +: ${RELEASE=NO} # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line # above. If this is not a released version, then we will append the From git at git.haskell.org Sun Jul 23 12:54:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Jul 2017 12:54:07 +0000 (UTC) Subject: [commit: ghc] tag 'ghc-8.2.1-release' created Message-ID: <20170723125407.232AC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New tag : ghc-8.2.1-release Referencing: 646fc7afed4288ebf7ac5be75d32dfd8e74482fa From git at git.haskell.org Sun Jul 23 14:14:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Jul 2017 14:14:39 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Add some missing release notes entries (d3857ba) Message-ID: <20170723141439.A46AC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/d3857ba405725e03b7fef9516f8a4bf62a247f91/ghc >--------------------------------------------------------------- commit d3857ba405725e03b7fef9516f8a4bf62a247f91 Author: Ben Gamari Date: Sun Jul 23 09:29:06 2017 -0400 Add some missing release notes entries >--------------------------------------------------------------- d3857ba405725e03b7fef9516f8a4bf62a247f91 docs/users_guide/8.2.1-notes.rst | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index 2aef7d4..e165998 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -31,6 +31,12 @@ The highlights since the 8.0 release include: Full details ------------ +Package system +~~~~~~~~~~~~~~ + +- The long awaited Backpack module system is now fully usable. See + :ghc-wiki:`the GHC Wiki ` for details. + Language ~~~~~~~~ @@ -41,6 +47,12 @@ Language class instance using the :ghc-flag:`-XDerivingStrategies` language extension (see :ref:`deriving-strategies`). +- The new :ghc-flag:`-XUnboxedSums` extension allows more efficient representation + of sum data. Some future GHC release will have support for worker/wrapper + transformation of sum arguments and constructor unpacking. + +- Support for overloaded record fields via a new ``HasField`` class and + associated compiler logic (see :ref:`record-field-selector-polymorphism`) Compiler ~~~~~~~~ From git at git.haskell.org Sun Jul 23 14:14:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Jul 2017 14:14:42 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix links to SPJ’s papers (fixes #12578) (834e350) Message-ID: <20170723141442.654163A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/834e350bd9b54bf465f2fef880e18f412fea57d3/ghc >--------------------------------------------------------------- commit 834e350bd9b54bf465f2fef880e18f412fea57d3 Author: Takenobu Tani Date: Wed Jul 19 15:06:27 2017 -0400 Fix links to SPJ’s papers (fixes #12578) This fixes #12578. Update links to SPJ's papers in following files: * compiler/coreSyn/CoreSyn.hs * docs/users_guide/using-optimisation.rst * docs/users_guide/parallel.rst * docs/users_guide/glasgow_exts.rst This commit is for ghc-8.2 branch. Test Plan: build Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #12578 Differential Revision: https://phabricator.haskell.org/D3745 (cherry picked from commit 1ed41a7413a45e11a9bad3aafcfb7ee3f26236e4) >--------------------------------------------------------------- 834e350bd9b54bf465f2fef880e18f412fea57d3 compiler/coreSyn/CoreSyn.hs | 2 +- docs/users_guide/glasgow_exts.rst | 8 ++++---- docs/users_guide/parallel.rst | 4 ++-- docs/users_guide/using-optimisation.rst | 2 +- 4 files changed, 8 insertions(+), 8 deletions(-) diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs index 0590b19..9dd665e 100644 --- a/compiler/coreSyn/CoreSyn.hs +++ b/compiler/coreSyn/CoreSyn.hs @@ -137,7 +137,7 @@ These data types are the heart of the compiler -} -- | This is the data type that represents GHCs core intermediate language. Currently --- GHC uses System FC for this purpose, +-- GHC uses System FC for this purpose, -- which is closely related to the simpler and better known System F . -- -- We get from Haskell source to this Core language in a number of stages: diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 3dc64af..a98e724 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -1109,7 +1109,7 @@ Generalised list comprehensions are a further enhancement to the list comprehension syntactic sugar to allow operations such as sorting and grouping which are familiar from SQL. They are fully described in the paper `Comprehensive comprehensions: comprehensions with "order by" and -"group by" `__, +"group by" `__, except that the syntax we use differs slightly from the paper. The extension is enabled with the flag :ghc-flag:`-XTransformListComp`. @@ -5703,7 +5703,7 @@ reduction step makes the problem smaller by at least one constructor. You can find lots of background material about the reason for these restrictions in the paper `Understanding functional dependencies via Constraint Handling -Rules `__. +Rules `__. For example, these are okay: @@ -9246,7 +9246,7 @@ restriction is not closed, and hence may in turn prevent generalisation of bindings that mention it. The rationale for this more conservative strategy is given in `the -papers `__ +papers `__ "Let should not be generalised" and "Modular type inference with local assumptions", and a related `blog post `__. @@ -10519,7 +10519,7 @@ ignore the problems in ``a``. For more motivation and details please refer to the :ghc-wiki:`Wiki ` page or the `original -paper `__. +paper `__. Enabling deferring of type errors --------------------------------- diff --git a/docs/users_guide/parallel.rst b/docs/users_guide/parallel.rst index 07dc60f..bac7754 100644 --- a/docs/users_guide/parallel.rst +++ b/docs/users_guide/parallel.rst @@ -47,14 +47,14 @@ The functions exported by this library include: - Synchronised mutable variables, called ``MVars`` - Support for bound threads; see the paper `Extending the FFI with - concurrency `__. + concurrency `__. Software Transactional Memory ----------------------------- GHC now supports a new way to coordinate the activities of Concurrent Haskell threads, called Software Transactional Memory (STM). The `STM -papers `__ +papers `__ are an excellent introduction to what STM is, and how to use it. The main library you need to use is the `stm diff --git a/docs/users_guide/using-optimisation.rst b/docs/users_guide/using-optimisation.rst index e2e7887..4df2a5b 100644 --- a/docs/users_guide/using-optimisation.rst +++ b/docs/users_guide/using-optimisation.rst @@ -230,7 +230,7 @@ by saying ``-fno-wombat``. Usually GHC black-holes a thunk only when it switches threads. This flag makes it do so as soon as the thunk is entered. See `Haskell on a shared-memory - multiprocessor `__. + multiprocessor `__. .. ghc-flag:: -fexcess-precision From git at git.haskell.org Sun Jul 23 16:55:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Jul 2017 16:55:00 +0000 (UTC) Subject: [commit: ghc] master: Update autoconf scripts (ee1047e) Message-ID: <20170723165500.837B13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ee1047e2283a3f628fd0d91df0e9eb955bb0994d/ghc >--------------------------------------------------------------- commit ee1047e2283a3f628fd0d91df0e9eb955bb0994d Author: Ben Gamari Date: Fri Jul 21 17:59:22 2017 -0400 Update autoconf scripts Scripts taken from autoconf 81497f5aaf50a12a9fe0cba30ef18bda46b62959 >--------------------------------------------------------------- ee1047e2283a3f628fd0d91df0e9eb955bb0994d config.guess | 17 ++++++++++++----- libraries/base/config.guess | 17 ++++++++++++----- libraries/integer-gmp/config.guess | 17 ++++++++++++----- 3 files changed, 36 insertions(+), 15 deletions(-) diff --git a/config.guess b/config.guess index faa63aa..07785f5 100755 --- a/config.guess +++ b/config.guess @@ -2,7 +2,7 @@ # Attempt to guess a canonical system name. # Copyright 1992-2017 Free Software Foundation, Inc. -timestamp='2017-05-11' +timestamp='2017-07-19' # This file is free software; you can redistribute it and/or modify it # under the terms of the GNU General Public License as published by @@ -1304,14 +1304,21 @@ EOF if test `echo "$UNAME_RELEASE" | sed -e 's/\..*//'` -le 10 ; then if [ "$CC_FOR_BUILD" != no_compiler_found ]; then if (echo '#ifdef __LP64__'; echo IS_64BIT_ARCH; echo '#endif') | \ - (CCOPTS="" $CC_FOR_BUILD -E - 2>/dev/null) | \ - grep IS_64BIT_ARCH >/dev/null + (CCOPTS="" $CC_FOR_BUILD -E - 2>/dev/null) | \ + grep IS_64BIT_ARCH >/dev/null then case $UNAME_PROCESSOR in i386) UNAME_PROCESSOR=x86_64 ;; powerpc) UNAME_PROCESSOR=powerpc64 ;; esac fi + # On 10.4-10.6 one might compile for PowerPC via gcc -arch ppc + if (echo '#ifdef __POWERPC__'; echo IS_PPC; echo '#endif') | \ + (CCOPTS="" $CC_FOR_BUILD -E - 2>/dev/null) | \ + grep IS_PPC >/dev/null + then + UNAME_PROCESSOR=powerpc + fi fi elif test "$UNAME_PROCESSOR" = i386 ; then # Avoid executing cc on OS X 10.9, as it ships with a stub @@ -1422,8 +1429,8 @@ cat >&2 </dev/null) | \ - grep IS_64BIT_ARCH >/dev/null + (CCOPTS="" $CC_FOR_BUILD -E - 2>/dev/null) | \ + grep IS_64BIT_ARCH >/dev/null then case $UNAME_PROCESSOR in i386) UNAME_PROCESSOR=x86_64 ;; powerpc) UNAME_PROCESSOR=powerpc64 ;; esac fi + # On 10.4-10.6 one might compile for PowerPC via gcc -arch ppc + if (echo '#ifdef __POWERPC__'; echo IS_PPC; echo '#endif') | \ + (CCOPTS="" $CC_FOR_BUILD -E - 2>/dev/null) | \ + grep IS_PPC >/dev/null + then + UNAME_PROCESSOR=powerpc + fi fi elif test "$UNAME_PROCESSOR" = i386 ; then # Avoid executing cc on OS X 10.9, as it ships with a stub @@ -1422,8 +1429,8 @@ cat >&2 </dev/null) | \ - grep IS_64BIT_ARCH >/dev/null + (CCOPTS="" $CC_FOR_BUILD -E - 2>/dev/null) | \ + grep IS_64BIT_ARCH >/dev/null then case $UNAME_PROCESSOR in i386) UNAME_PROCESSOR=x86_64 ;; powerpc) UNAME_PROCESSOR=powerpc64 ;; esac fi + # On 10.4-10.6 one might compile for PowerPC via gcc -arch ppc + if (echo '#ifdef __POWERPC__'; echo IS_PPC; echo '#endif') | \ + (CCOPTS="" $CC_FOR_BUILD -E - 2>/dev/null) | \ + grep IS_PPC >/dev/null + then + UNAME_PROCESSOR=powerpc + fi fi elif test "$UNAME_PROCESSOR" = i386 ; then # Avoid executing cc on OS X 10.9, as it ships with a stub @@ -1422,8 +1429,8 @@ cat >&2 < Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/98ab12ad0c13b6723cc667d6a00fe592f1833bf4/ghc >--------------------------------------------------------------- commit 98ab12ad0c13b6723cc667d6a00fe592f1833bf4 Author: Ben Gamari Date: Sun Jul 23 10:43:52 2017 -0400 distrib/configure: Carry FFI include/lib paths from source distribution `FFILibDir` and `FFIIncludeDir` both show up in the `rts` library's package registration file. We therefore must define them or else we'll end up with spurious `@FFILibDir@` strings in the package registration. In principle I think we could also take these as arguments to the bindist configure but this seems simpler and I don't want to verify this at the moment. Test Plan: Build bindist while passing `--with-ffi-libraries=...` to source distribution configure then try to install and use bindist. Reviewers: austin, hvr Subscribers: rwbarton, thomie, erikd Differential Revision: https://phabricator.haskell.org/D3774 >--------------------------------------------------------------- 98ab12ad0c13b6723cc667d6a00fe592f1833bf4 distrib/configure.ac.in | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index 314bb3a..8c7b226 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -12,8 +12,15 @@ dnl-------------------------------------------------------------------- FP_GMP +dnl Various things from the source distribution configure bootstrap_target=@TargetPlatform@ +FFIIncludeDir=@FFIIncludeDir@ +FFILibDir=@FFILibDir@ +AC_SUBST(FFILibDir) +AC_SUBST(FFIIncludeDir) + + # We have to run these unconditionally as FPTOOLS_SET_PLATFORM_VARS wants the # values it computes. AC_CANONICAL_BUILD From git at git.haskell.org Sun Jul 23 16:55:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Jul 2017 16:55:05 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Improve legibility of OverlappingInstances documentation (fb08252) Message-ID: <20170723165505.F3E193A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fb08252ae44dd39e5dcd0de8bd63843eb495f213/ghc >--------------------------------------------------------------- commit fb08252ae44dd39e5dcd0de8bd63843eb495f213 Author: Ben Gamari Date: Sun Jul 23 10:44:09 2017 -0400 users-guide: Improve legibility of OverlappingInstances documentation Reviewers: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3776 >--------------------------------------------------------------- fb08252ae44dd39e5dcd0de8bd63843eb495f213 docs/users_guide/glasgow_exts.rst | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 418e7cb..7953067 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -6044,16 +6044,16 @@ Now suppose that, in some client module, we are searching for an instance of the *target constraint* ``(C ty1 .. tyn)``. The search works like this: -- Find all instances I that *match* the target constraint; that is, the - target constraint is a substitution instance of I. These instance +- Find all instances :math:`I` that *match* the target constraint; that is, the + target constraint is a substitution instance of :math:`I`. These instance declarations are the *candidates*. -- Eliminate any candidate IX for which both of the following hold: +- Eliminate any candidate :math:`IX` for which both of the following hold: - - There is another candidate IY that is strictly more specific; that - is, IY is a substitution instance of IX but not vice versa. + - There is another candidate :math:`IY` that is strictly more specific; that + is, :math:`IY` is a substitution instance of :math:`IX` but not vice versa. - - Either IX is *overlappable*, or IY is *overlapping*. (This + - Either :math:`IX` is *overlappable*, or :math:`IY` is *overlapping*. (This "either/or" design, rather than a "both/and" design, allow a client to deliberately override an instance from a library, without requiring a change to the library.) From git at git.haskell.org Sun Jul 23 16:55:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Jul 2017 16:55:08 +0000 (UTC) Subject: [commit: ghc] master: Preserve HaskellHaveRTSLinker in bindist (0ae0f46) Message-ID: <20170723165508.D8D853A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0ae0f466902dff493cd5104872289834819c6a5f/ghc >--------------------------------------------------------------- commit 0ae0f466902dff493cd5104872289834819c6a5f Author: Ben Gamari Date: Sun Jul 23 10:45:07 2017 -0400 Preserve HaskellHaveRTSLinker in bindist Otherwise you end up with ("target has RTS linker","@HaskellHaveRTSLinker@") in the installed settings file. >--------------------------------------------------------------- 0ae0f466902dff493cd5104872289834819c6a5f distrib/configure.ac.in | 3 +++ 1 file changed, 3 insertions(+) diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index 8c7b226..7c27dad 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -15,6 +15,9 @@ FP_GMP dnl Various things from the source distribution configure bootstrap_target=@TargetPlatform@ +HaskellHaveRTSLinker=@HaskellHaveRTSLinker@ +AC_SUBST(HaskellHaveRTSLinker) + FFIIncludeDir=@FFIIncludeDir@ FFILibDir=@FFILibDir@ AC_SUBST(FFILibDir) From git at git.haskell.org Sun Jul 23 16:55:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Jul 2017 16:55:14 +0000 (UTC) Subject: [commit: ghc] master: Update release notes for 8.2.1 (b8afdaf) Message-ID: <20170723165514.58F6E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b8afdafc940b40385e3372741589e7c7372a95fe/ghc >--------------------------------------------------------------- commit b8afdafc940b40385e3372741589e7c7372a95fe Author: Ben Gamari Date: Mon Jul 10 16:41:42 2017 -0400 Update release notes for 8.2.1 This pulls over changes that were made in the ghc-8.2 branch. >--------------------------------------------------------------- b8afdafc940b40385e3372741589e7c7372a95fe docs/users_guide/8.2.1-notes.rst | 203 ++++++++++++++++++++------------------- 1 file changed, 105 insertions(+), 98 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b8afdafc940b40385e3372741589e7c7372a95fe From git at git.haskell.org Sun Jul 23 16:55:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Jul 2017 16:55:11 +0000 (UTC) Subject: [commit: ghc] master: Bump a bunch of submodules (646ec0e) Message-ID: <20170723165511.95DAB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/646ec0e341c63dc6ba12f5e7f45e43a944d86a62/ghc >--------------------------------------------------------------- commit 646ec0e341c63dc6ba12f5e7f45e43a944d86a62 Author: Ben Gamari Date: Sun Jul 23 11:21:41 2017 -0400 Bump a bunch of submodules >--------------------------------------------------------------- 646ec0e341c63dc6ba12f5e7f45e43a944d86a62 libraries/Cabal | 2 +- libraries/Win32 | 2 +- libraries/binary | 2 +- libraries/deepseq | 2 +- libraries/parallel | 2 +- libraries/process | 2 +- libraries/time | 2 +- libraries/unix | 2 +- libraries/xhtml | 2 +- 9 files changed, 9 insertions(+), 9 deletions(-) diff --git a/libraries/Cabal b/libraries/Cabal index ece0273..082cf20 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit ece0273b48b7ff19fff6cd82913717d86d3ffbfa +Subproject commit 082cf2066b7206d3b12a9f92d832236e2484b4c1 diff --git a/libraries/Win32 b/libraries/Win32 index b5ebb64..147a0af 160000 --- a/libraries/Win32 +++ b/libraries/Win32 @@ -1 +1 @@ -Subproject commit b5ebb64894cf166f9ee84ee91802486c76e480cf +Subproject commit 147a0af92ac74ec58b209e16aeb1cf03bddf9482 diff --git a/libraries/binary b/libraries/binary index 0147456..d4a030a 160000 --- a/libraries/binary +++ b/libraries/binary @@ -1 +1 @@ -Subproject commit 0147456b11c38d1121fd84a2b53effefde111240 +Subproject commit d4a030ab448191f664fc734bfbee61450a6fa5af diff --git a/libraries/deepseq b/libraries/deepseq index 65dd864..0b22c98 160000 --- a/libraries/deepseq +++ b/libraries/deepseq @@ -1 +1 @@ -Subproject commit 65dd864d0d2f5cf415064fc214261b9270a924cf +Subproject commit 0b22c9825ef79c1ee41d2f19e7c997f5cdc93494 diff --git a/libraries/parallel b/libraries/parallel index 040c4f0..d2e2a5e 160000 --- a/libraries/parallel +++ b/libraries/parallel @@ -1 +1 @@ -Subproject commit 040c4f0226a5a9a1e720d89a9e1239028d9f62d9 +Subproject commit d2e2a5e630fdfa0e9bc8c2d8c7d134ad3500b5de diff --git a/libraries/process b/libraries/process index 88547b0..423a9ef 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit 88547b0fae8644f8f69be32c7ee5a3b76051c82f +Subproject commit 423a9efa8b1b22304af0acc8b950289026b288eb diff --git a/libraries/time b/libraries/time index d03429e..1fcaa07 160000 --- a/libraries/time +++ b/libraries/time @@ -1 +1 @@ -Subproject commit d03429e1913b6babd3b59d0bfdd7d3904b1b6f0b +Subproject commit 1fcaa07e10d7966356373ed0e946eb078fcdd6e6 diff --git a/libraries/unix b/libraries/unix index eb5fc94..fcaa530 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit eb5fc942f8f570e754bba0f57a8fdaec3400194f +Subproject commit fcaa530a8fdd3897353bdf246752a91d675aad46 diff --git a/libraries/xhtml b/libraries/xhtml index 8a8c8a4..6358594 160000 --- a/libraries/xhtml +++ b/libraries/xhtml @@ -1 +1 @@ -Subproject commit 8a8c8a48bac2d3ed306b610a2e9fa393b5a7ffa5 +Subproject commit 6358594eb5139f6760e2ada72718d69fed5a1015 From git at git.haskell.org Sun Jul 23 16:55:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Jul 2017 16:55:17 +0000 (UTC) Subject: [commit: ghc] master: Bump integer-gmp version (fb17cc5) Message-ID: <20170723165517.199B93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fb17cc54d86173bf633ed0b598d82ffb1a38c8fd/ghc >--------------------------------------------------------------- commit fb17cc54d86173bf633ed0b598d82ffb1a38c8fd Author: Ben Gamari Date: Fri Jul 21 17:31:03 2017 -0400 Bump integer-gmp version (cherry picked from commit 09396ec3bb672e761c3e627484dd02c5a3a76c77) >--------------------------------------------------------------- fb17cc54d86173bf633ed0b598d82ffb1a38c8fd libraries/integer-gmp/changelog.md | 8 +++++++- libraries/integer-gmp/integer-gmp.cabal | 2 +- testsuite/tests/determinism/determ021/determ021.stdout | 4 ++-- 3 files changed, 10 insertions(+), 4 deletions(-) diff --git a/libraries/integer-gmp/changelog.md b/libraries/integer-gmp/changelog.md index cdee847..b817881 100644 --- a/libraries/integer-gmp/changelog.md +++ b/libraries/integer-gmp/changelog.md @@ -1,9 +1,15 @@ # Changelog for [`integer-gmp` package](http://hackage.haskell.org/package/integer-gmp) -## 1.0.0.2 *TBA* +## 1.0.1.0 *July 2017* + + * Bundled with GHC 8.2.1 * Optimize `minusInteger` + * Fix the right-shift operation for negative big integers (fixes GHC #12136) + + * Make operations more strict + ## 1.0.0.1 *Feb 2016* * Bundled with GHC 8.0.1 diff --git a/libraries/integer-gmp/integer-gmp.cabal b/libraries/integer-gmp/integer-gmp.cabal index 377efb3..2f32b34 100644 --- a/libraries/integer-gmp/integer-gmp.cabal +++ b/libraries/integer-gmp/integer-gmp.cabal @@ -1,5 +1,5 @@ name: integer-gmp -version: 1.0.0.1 +version: 1.0.1.0 synopsis: Integer library based on GMP license: BSD3 license-file: LICENSE diff --git a/testsuite/tests/determinism/determ021/determ021.stdout b/testsuite/tests/determinism/determ021/determ021.stdout index bc5b5cd..d866212 100644 --- a/testsuite/tests/determinism/determ021/determ021.stdout +++ b/testsuite/tests/determinism/determ021/determ021.stdout @@ -8,7 +8,7 @@ TYPE CONSTRUCTORS COERCION AXIOMS Dependent modules: [] Dependent packages: [base-4.10.0.0, ghc-prim-0.5.0.0, - integer-gmp-1.0.0.1] + integer-gmp-1.0.1.0] [1 of 1] Compiling A ( A.hs, A.o ) TYPE SIGNATURES test2 :: @@ -19,4 +19,4 @@ TYPE CONSTRUCTORS COERCION AXIOMS Dependent modules: [] Dependent packages: [base-4.10.0.0, ghc-prim-0.5.0.0, - integer-gmp-1.0.0.1] + integer-gmp-1.0.1.0] From git at git.haskell.org Sun Jul 23 16:55:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Jul 2017 16:55:19 +0000 (UTC) Subject: [commit: ghc] master: ghc-prim: Bump version (ecc9e9a) Message-ID: <20170723165519.E10D63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ecc9e9aaaf6e74a0a7f90cfa5700f99e385d0d85/ghc >--------------------------------------------------------------- commit ecc9e9aaaf6e74a0a7f90cfa5700f99e385d0d85 Author: Ben Gamari Date: Thu Jul 20 11:27:45 2017 -0400 ghc-prim: Bump version (cherry picked from commit 8c5405f63c2de0c445ec171aab63c35786544b9e) >--------------------------------------------------------------- ecc9e9aaaf6e74a0a7f90cfa5700f99e385d0d85 libraries/ghc-compact/ghc-compact.cabal | 2 +- libraries/ghc-prim/ghc-prim.cabal | 2 +- testsuite/tests/ado/ado004.stderr | 2 +- testsuite/tests/backpack/should_compile/bkp16.stderr | 2 +- testsuite/tests/determinism/determ021/determ021.stdout | 4 ++-- testsuite/tests/driver/json2.stderr | 4 ++-- testsuite/tests/indexed-types/should_compile/T3017.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ADT.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr1.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr2.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr3.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr4.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr5.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/AddAndOr6.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/BoolToBool.stderr | 2 +- .../tests/partial-sigs/should_compile/DataFamilyInstanceLHS.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Defaulting1MROn.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Defaulting2MROff.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Defaulting2MROn.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Either.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/EqualityConstraint.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Every.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/EveryNamed.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ExpressionSig.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ExpressionSigNamed.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ExtraConstraints1.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ExtraConstraints2.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ExtraConstraints3.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROff.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROn.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Forall1.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/GenNamed.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/HigherRank1.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/HigherRank2.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/LocalDefinitionBug.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Meltdown.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/MonoLocalBinds.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/NamedTyVar.stderr | 2 +- .../should_compile/NamedWildcardInDataFamilyInstanceLHS.stderr | 2 +- .../should_compile/NamedWildcardInTypeFamilyInstanceLHS.stderr | 2 +- .../tests/partial-sigs/should_compile/ParensAroundContext.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/PatBind.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/PatBind2.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/PatternSig.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Recursive.stderr | 2 +- .../tests/partial-sigs/should_compile/ScopedNamedWildcards.stderr | 2 +- .../tests/partial-sigs/should_compile/ScopedNamedWildcardsGood.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ShowNamed.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/SimpleGen.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/SkipMany.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/SomethingShowable.stderr | 2 +- .../tests/partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Uncurry.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/UncurryNamed.stderr | 2 +- .../partial-sigs/should_compile/WarningWildcardInstantiations.stderr | 2 +- testsuite/tests/roles/should_compile/Roles1.stderr | 2 +- testsuite/tests/roles/should_compile/Roles14.stderr | 2 +- testsuite/tests/roles/should_compile/Roles2.stderr | 2 +- testsuite/tests/roles/should_compile/Roles3.stderr | 2 +- testsuite/tests/roles/should_compile/Roles4.stderr | 2 +- testsuite/tests/roles/should_compile/T8958.stderr | 2 +- testsuite/tests/typecheck/should_compile/T12763.stderr | 2 +- testsuite/tests/typecheck/should_compile/tc231.stderr | 2 +- 63 files changed, 65 insertions(+), 65 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 ecc9e9aaaf6e74a0a7f90cfa5700f99e385d0d85 From git at git.haskell.org Sun Jul 23 16:55:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Jul 2017 16:55:22 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Fix cabal01 for real this time (d4e9721) Message-ID: <20170723165522.9CD283A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d4e97212fdcb6127d750577aa7f2d709fee27d56/ghc >--------------------------------------------------------------- commit d4e97212fdcb6127d750577aa7f2d709fee27d56 Author: Ben Gamari Date: Fri Jun 23 14:47:06 2017 -0400 testsuite: Fix cabal01 for real this time Somehow the previous version passed on master but fails on ghc-8.2. Will look deeper later. (cherry picked from commit a6774e1d70f18f5c05279453d62fb3bcc7f07d7e) >--------------------------------------------------------------- d4e97212fdcb6127d750577aa7f2d709fee27d56 testsuite/tests/cabal/cabal01/test.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/cabal/cabal01/test.cabal b/testsuite/tests/cabal/cabal01/test.cabal index fe66d70..b5c3b74 100644 --- a/testsuite/tests/cabal/cabal01/test.cabal +++ b/testsuite/tests/cabal/cabal01/test.cabal @@ -12,5 +12,5 @@ Main-is: MainA.hs Extensions: OverlappingInstances Executable: testB -Other-Modules: B.A +Other-Modules: A, B.A Main-is: B/MainB.hs From git at git.haskell.org Sun Jul 23 19:47:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Jul 2017 19:47:41 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Standardize and repair all flag references (44b090b) Message-ID: <20170723194741.A1F163A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/44b090be9a6d0165e2281542a7c713da1799e885/ghc >--------------------------------------------------------------- commit 44b090be9a6d0165e2281542a7c713da1799e885 Author: Patrick Dougherty Date: Sun Jul 23 12:55:37 2017 -0400 users-guide: Standardize and repair all flag references This patch does three things: 1.) It simplifies the flag parsing code in `conf.py` to properly display flag definitions created by `.. (ghc|rts)-flag::`. Additionally, all flag references must include the associated arguments. Documentation has been added to `editing-guide.rst` to explain this. 2.) It normalizes all flag definitions to a similar format. Notably, all instances of `<>` have been replaced with `⟨⟩`. All references across the users guide have been updated to match. 3.) It fixes a couple issues with the flag reference table's generation code, which did not handle comma separated flags in the same cell and did not properly reference flags with arguments. Test Plan: `SPHINXOPTS = -n` to activate "nitpicky" mode, which reports all broken references. All remaining errors are references to flags without any documentation. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13980 Differential Revision: https://phabricator.haskell.org/D3778 >--------------------------------------------------------------- 44b090be9a6d0165e2281542a7c713da1799e885 docs/users_guide/8.2.1-notes.rst | 4 +- docs/users_guide/conf.py | 52 ++++--- docs/users_guide/debug-info.rst | 3 +- docs/users_guide/debugging.rst | 8 +- docs/users_guide/editing-guide.rst | 26 +++- docs/users_guide/extending_ghc.rst | 65 ++++----- docs/users_guide/ffi-chap.rst | 14 +- docs/users_guide/ghci.rst | 38 ++--- docs/users_guide/glasgow_exts.rst | 44 +++--- docs/users_guide/packages.rst | 82 +++++------ docs/users_guide/phases.rst | 86 +++++------ docs/users_guide/profiling.rst | 89 +++++++----- docs/users_guide/runtime_control.rst | 161 +++++++++------------ docs/users_guide/separate_compilation.rst | 48 +++--- docs/users_guide/shared_libs.rst | 21 ++- docs/users_guide/sooner.rst | 34 ++--- docs/users_guide/using-concurrent.rst | 18 +-- docs/users_guide/using-optimisation.rst | 55 +++---- docs/users_guide/using-warnings.rst | 6 +- docs/users_guide/using.rst | 21 +-- utils/mkUserGuidePart/Main.hs | 9 +- utils/mkUserGuidePart/Options/CompilerDebugging.hs | 4 +- utils/mkUserGuidePart/Options/FindingImports.hs | 2 +- utils/mkUserGuidePart/Options/Interactive.hs | 2 +- utils/mkUserGuidePart/Options/Linking.hs | 17 ++- utils/mkUserGuidePart/Options/Misc.hs | 5 +- utils/mkUserGuidePart/Options/Modes.hs | 4 +- utils/mkUserGuidePart/Options/Packages.hs | 30 ++-- utils/mkUserGuidePart/Options/PhasePrograms.hs | 24 +-- utils/mkUserGuidePart/Options/PhaseSpecific.hs | 20 +-- utils/mkUserGuidePart/Options/Phases.hs | 4 +- utils/mkUserGuidePart/Options/Plugin.hs | 2 +- utils/mkUserGuidePart/Options/ProgramCoverage.hs | 2 +- utils/mkUserGuidePart/Options/RedirectingOutput.hs | 10 +- utils/mkUserGuidePart/Options/Verbosity.hs | 2 +- utils/mkUserGuidePart/Options/Warnings.hs | 10 +- 36 files changed, 525 insertions(+), 497 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 44b090be9a6d0165e2281542a7c713da1799e885 From git at git.haskell.org Sun Jul 23 19:47:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Jul 2017 19:47:44 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Fix various wibbles (c945195) Message-ID: <20170723194744.6127E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c9451959d8796ee5458cd0666dd2bc2114ac10d7/ghc >--------------------------------------------------------------- commit c9451959d8796ee5458cd0666dd2bc2114ac10d7 Author: Ben Gamari Date: Sun Jul 23 12:59:49 2017 -0400 users-guide: Fix various wibbles >--------------------------------------------------------------- c9451959d8796ee5458cd0666dd2bc2114ac10d7 docs/users_guide/phases.rst | 2 +- docs/users_guide/profiling.rst | 19 +++++++++++-------- docs/users_guide/runtime_control.rst | 4 ++-- docs/users_guide/separate_compilation.rst | 6 +++--- 4 files changed, 17 insertions(+), 14 deletions(-) diff --git a/docs/users_guide/phases.rst b/docs/users_guide/phases.rst index 831ace4..1874262 100644 --- a/docs/users_guide/phases.rst +++ b/docs/users_guide/phases.rst @@ -545,7 +545,7 @@ for example). .. ghc-flag:: -L ⟨dir⟩ - Where to f ind user-supplied libraries… Prepend the directory ⟨dir⟩ + Where to find user-supplied libraries… Prepend the directory ⟨dir⟩ to the library directories path. .. ghc-flag:: -framework-path ⟨dir⟩ diff --git a/docs/users_guide/profiling.rst b/docs/users_guide/profiling.rst index 0a4ba09..e3796ed 100644 --- a/docs/users_guide/profiling.rst +++ b/docs/users_guide/profiling.rst @@ -429,6 +429,8 @@ enclosed between ``+RTS ... -RTS`` as usual): .. rts-flag:: -V ⟨secs⟩ + :default: 0.02 + Sets the interval that the RTS clock ticks at, which is also the sampling interval of the time and allocation profile. The default is 0.02 seconds. The runtime uses a single timer signal to count ticks; this timer signal is @@ -929,14 +931,15 @@ reasons for this: - Garbage collection requires more memory than the actual residency. The factor depends on the kind of garbage collection algorithm in use: a major GC - in the standard generation copying collector will usually require 3L bytes of - memory, where L is the amount of live data. This is because by default (see - the RTS :rts-flag:`-F ⟨factor⟩` option) we allow the old generation to grow - to twice its size (2L) before collecting it, and we require additionally L - bytes to copy the live data into. When using compacting collection (see the - :rts-flag:`-c` option), this is reduced to 2L, and can further be reduced by - tweaking the :rts-flag:`-F ⟨factor⟩` option. Also add the size of the - allocation area (see :rts-flag:`-A ⟨size⟩`). + in the standard generation copying collector will usually require :math:`3L` + bytes of memory, where :math:`L` is the amount of live data. This is because + by default (see the RTS :rts-flag:`-F ⟨factor⟩` option) we allow the old + generation to grow to twice its size (:math:`2L`) before collecting it, and + we require additionally :math:`L` bytes to copy the live data into. When + using compacting collection (see the :rts-flag:`-c` option), this is reduced + to :math:`2L`, and can further be reduced by tweaking the :rts-flag:`-F + ⟨factor⟩` option. Also add the size of the allocation area (see :rts-flag:`-A + ⟨size⟩`). - The stack isn't counted in the heap profile by default. See the RTS :rts-flag:`-xt` option. diff --git a/docs/users_guide/runtime_control.rst b/docs/users_guide/runtime_control.rst index 5286784..682ced8 100644 --- a/docs/users_guide/runtime_control.rst +++ b/docs/users_guide/runtime_control.rst @@ -253,7 +253,7 @@ Miscellaneous RTS options This option relates to allocation limits; for more about this see :base-ref:`enableAllocationLimit `. When a thread hits its allocation limit, the RTS throws an exception - to the thread, and the thread gets an additional quota of allo + to the thread, and the thread gets an additional quota of allocation before the exception is raised again, the idea being so that the thread can execute its exception handlers. The ``-xq`` controls the size of this additional quota. @@ -339,7 +339,7 @@ performance. .. index:: single: allocation area, chunk size - [Example: ``-n4m``\ ] When set to a non-zero value, this + [Example: ``-n4m`` ] When set to a non-zero value, this option divides the allocation area (``-A`` value) into chunks of the specified size. During execution, when a processor exhausts its current chunk, it is given another chunk from the pool until the diff --git a/docs/users_guide/separate_compilation.rst b/docs/users_guide/separate_compilation.rst index 04ef591..06af6f0 100644 --- a/docs/users_guide/separate_compilation.rst +++ b/docs/users_guide/separate_compilation.rst @@ -1190,8 +1190,8 @@ generation are: .. ghc-flag:: -dep-suffix ⟨suffix⟩ Make dependencies that declare that files with suffix - ``.`` depend on interface files with suffix - ``.hi``, or (for ``{-# SOURCE #-}`` imports) on ``.hi-boot``. + ``.⟨suf⟩⟨osuf⟩`` depend on interface files with suffix + ``.⟨suf⟩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`` on ``.hi``, ``.a_hs`` on ``.a_hi``, and ``.b_hs`` on ``.b_hi``. @@ -1200,7 +1200,7 @@ generation are: .. ghc-flag:: --exclude-module=⟨file⟩ - Regard ```` as "stable"; i.e., exclude it from having + Regard ``⟨file⟩`` as "stable"; i.e., exclude it from having dependencies on it. .. ghc-flag:: -include-pkg-deps From git at git.haskell.org Sun Jul 23 19:47:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Jul 2017 19:47:47 +0000 (UTC) Subject: [commit: ghc] master: Fix more documentation wibbles (2dff2c7) Message-ID: <20170723194747.35DF43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2dff2c7fbb5aa68445e617d691451c0427fad0a5/ghc >--------------------------------------------------------------- commit 2dff2c7fbb5aa68445e617d691451c0427fad0a5 Author: Ben Gamari Date: Sun Jul 23 14:13:16 2017 -0400 Fix more documentation wibbles Fixes #14020, #14016, #14015, #14019 >--------------------------------------------------------------- 2dff2c7fbb5aa68445e617d691451c0427fad0a5 docs/users_guide/8.0.2-notes.rst | 2 +- docs/users_guide/8.2.1-notes.rst | 17 ++--- docs/users_guide/conf.py | 2 +- docs/users_guide/editing-guide.rst | 15 +++++ docs/users_guide/ffi-chap.rst | 5 +- docs/users_guide/ghc_config.py.in | 8 ++- docs/users_guide/ghci.rst | 5 ++ docs/users_guide/glasgow_exts.rst | 45 +++++++------ docs/users_guide/packages.rst | 2 +- docs/users_guide/parallel.rst | 8 +-- docs/users_guide/phases.rst | 13 ++-- docs/users_guide/profiling.rst | 11 +++- docs/users_guide/runghc.rst | 2 +- docs/users_guide/runtime_control.rst | 98 +++++++++++++--------------- docs/users_guide/safe_haskell.rst | 2 +- docs/users_guide/sooner.rst | 2 +- docs/users_guide/using-concurrent.rst | 18 ++--- docs/users_guide/using-warnings.rst | 13 ++-- docs/users_guide/using.rst | 12 ++-- utils/mkUserGuidePart/Options/Interactive.hs | 2 +- utils/mkUserGuidePart/Options/Verbosity.hs | 2 +- 21 files changed, 165 insertions(+), 119 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 2dff2c7fbb5aa68445e617d691451c0427fad0a5 From git at git.haskell.org Mon Jul 24 15:55:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Jul 2017 15:55:22 +0000 (UTC) Subject: [commit: ghc] master: Remove 8.0.2 release notes file (145f1c7) Message-ID: <20170724155522.D57963A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/145f1c7f2367ff8404905fc8eca8de902711d05e/ghc >--------------------------------------------------------------- commit 145f1c7f2367ff8404905fc8eca8de902711d05e Author: Ryan Scott Date: Mon Jul 24 11:54:28 2017 -0400 Remove 8.0.2 release notes file Summary: Some summer cleaning. Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3783 >--------------------------------------------------------------- 145f1c7f2367ff8404905fc8eca8de902711d05e docs/users_guide/8.0.2-notes.rst | 207 --------------------------------------- 1 file changed, 207 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 145f1c7f2367ff8404905fc8eca8de902711d05e From git at git.haskell.org Mon Jul 24 15:55:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Jul 2017 15:55:25 +0000 (UTC) Subject: [commit: ghc] master: Add a caveat to the GHC.Generics examples about :+: nesting (88f20bd) Message-ID: <20170724155525.9C0AC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/88f20bdb60fb9469fa8ae953f7c2509d1913fdf7/ghc >--------------------------------------------------------------- commit 88f20bdb60fb9469fa8ae953f7c2509d1913fdf7 Author: Ryan Scott Date: Mon Jul 24 11:54:37 2017 -0400 Add a caveat to the GHC.Generics examples about :+: nesting Summary: GHC's choice in how it nests `:+:` can sometimes affect the implementaiton of `GHC.Generics`-related code, so we should make a note of this in the examples we provide. Fixes #9453. Test Plan: Read it, like it, build it, ship it Reviewers: bgamari, austin, hvr Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #9453 Differential Revision: https://phabricator.haskell.org/D3782 >--------------------------------------------------------------- 88f20bdb60fb9469fa8ae953f7c2509d1913fdf7 docs/users_guide/glasgow_exts.rst | 15 +++++++++-- libraries/base/GHC/Generics.hs | 52 ++++++++++++++++++++++----------------- 2 files changed, 43 insertions(+), 24 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index fddf993..eb99959 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -14025,8 +14025,19 @@ we show generic serialization: :: instance (Serialize a) => GSerialize (K1 i a) where gput (K1 x) = put x -Typically this class will not be exported, as it only makes sense to -have instances for the representation types. +A caveat: this encoding strategy may not be reliable across different versions +of GHC. When deriving a ``Generic`` instance is free to choose any nesting of +``:+:`` and ``:*:`` it chooses, so if GHC chooses ``(a :+: b) :+: c``, then the +encoding for ``a`` would be ``[O, O]``, ``b`` would be ``[O, I]``, and ``c`` +would be ``[I]``. However, if GHC chooses ``a :+: (b :+: c)``, then the +encoding for ``a`` would be ``[O]``, ``b`` would be ``[I, O]``, and ``c`` would +be ``[I, I]``. (In practice, the current implementation tries to produce a +more-or-less balanced nesting of ``:+:`` and ``:*:`` so that the traversal of +the structure of the datatype from the root to a particular component can be +performed in logarithmic rather than linear time.) + +Typically this ``GSerialize`` class will not be exported, as it only makes +sense to have instances for the representation types. Unlifted representation types ----------------------------- diff --git a/libraries/base/GHC/Generics.hs b/libraries/base/GHC/Generics.hs index cc85a1d..14184c2 100644 --- a/libraries/base/GHC/Generics.hs +++ b/libraries/base/GHC/Generics.hs @@ -1,23 +1,23 @@ -{-# LANGUAGE CPP #-} -{-# LANGUAGE DataKinds #-} -{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE GADTs #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} -{-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE FlexibleContexts #-} -{-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE GADTs #-} -{-# LANGUAGE KindSignatures #-} -{-# LANGUAGE MagicHash #-} -{-# LANGUAGE NoImplicitPrelude #-} -{-# LANGUAGE PolyKinds #-} -{-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE StandaloneDeriving #-} -{-# LANGUAGE Trustworthy #-} -{-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE TypeInType #-} -{-# LANGUAGE TypeOperators #-} -{-# LANGUAGE TypeSynonymInstances #-} -{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE KindSignatures #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeInType #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE TypeSynonymInstances #-} +{-# LANGUAGE UndecidableInstances #-} ----------------------------------------------------------------------------- -- | @@ -256,9 +256,9 @@ module GHC.Generics ( -- all the constructors and fields as needed. However, users /should not rely on -- a specific nesting strategy/ for ':+:' and ':*:' being used. The compiler is -- free to choose any nesting it prefers. (In practice, the current implementation --- tries to produce a more or less balanced nesting, so that the traversal of the --- structure of the datatype from the root to a particular component can be performed --- in logarithmic rather than linear time.) +-- tries to produce a more-or-less balanced nesting, so that the traversal of +-- the structure of the datatype from the root to a particular component can be +-- performed in logarithmic rather than linear time.) -- ** Defining datatype-generic functions -- @@ -351,6 +351,14 @@ module GHC.Generics ( -- encode' ('R1' x) = True : encode' x -- @ -- +-- (Note that this encoding strategy may not be reliable across different +-- versions of GHC. Recall that the compiler is free to choose any nesting +-- of ':+:' it chooses, so if GHC chooses @(a ':+:' b) ':+:' c@, then the +-- encoding for @a@ would be @[False, False]@, @b@ would be @[False, True]@, +-- and @c@ would be @[True]@. However, if GHC chooses @a ':+:' (b ':+:' c)@, +-- then the encoding for @a@ would be @[False]@, @b@ would be @[True, False]@, +-- and @c@ would be @[True, True]@.) +-- -- In the case for ':*:', we append the encodings of the two subcomponents: -- -- @ From git at git.haskell.org Mon Jul 24 19:31:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Jul 2017 19:31:23 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Changed perf_notes quite a bit. Should be much closer to actually usable now (4ff15ee) Message-ID: <20170724193123.19A3E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/4ff15ee25857010f9e4a58d8993c6bf5df583450/ghc >--------------------------------------------------------------- commit 4ff15ee25857010f9e4a58d8993c6bf5df583450 Author: Jared Weakly Date: Sat Jul 22 20:18:22 2017 -0700 Changed perf_notes quite a bit. Should be much closer to actually usable now >--------------------------------------------------------------- 4ff15ee25857010f9e4a58d8993c6bf5df583450 testsuite/driver/perf_notes.py | 84 +++++++++++++++++++++++++++++++++++++++--- testsuite/driver/runtests.py | 24 ++++++++++++ testsuite/driver/test_val | 76 ++++++++++++++++++++++++++++++++++++++ 3 files changed, 179 insertions(+), 5 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 4ff15ee25857010f9e4a58d8993c6bf5df583450 From git at git.haskell.org Mon Jul 24 19:31:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Jul 2017 19:31:25 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Cleaning up my trash code for the perf_notes comparison tool (809165b) Message-ID: <20170724193125.D5FE53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/809165b54e8881ef51879ba54acc8d5a4d02b5ee/ghc >--------------------------------------------------------------- commit 809165b54e8881ef51879ba54acc8d5a4d02b5ee Author: Jared Weakly Date: Sat Jul 22 20:48:48 2017 -0700 Cleaning up my trash code for the perf_notes comparison tool >--------------------------------------------------------------- 809165b54e8881ef51879ba54acc8d5a4d02b5ee testsuite/driver/perf_notes.py | 105 +++++++++++++---------------------------- 1 file changed, 34 insertions(+), 71 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 809165b54e8881ef51879ba54acc8d5a4d02b5ee From git at git.haskell.org Mon Jul 24 23:36:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Jul 2017 23:36:25 +0000 (UTC) Subject: [commit: ghc] master: users-guides: Fix errant whitespace (a602b65) Message-ID: <20170724233625.37F033A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a602b654992290c735cb65cb0dbabf07891e3920/ghc >--------------------------------------------------------------- commit a602b654992290c735cb65cb0dbabf07891e3920 Author: Ben Gamari Date: Sun Jul 23 15:48:56 2017 -0400 users-guides: Fix errant whitespace [skip-ci] >--------------------------------------------------------------- a602b654992290c735cb65cb0dbabf07891e3920 docs/users_guide/runtime_control.rst | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/runtime_control.rst b/docs/users_guide/runtime_control.rst index b3ab08f..5f64409 100644 --- a/docs/users_guide/runtime_control.rst +++ b/docs/users_guide/runtime_control.rst @@ -643,7 +643,7 @@ performance. ``-F`` parameter will be reduced in order to avoid exceeding the maximum heap size. -.. rts-flag:: -Mgrace= ⟨size⟩ +.. rts-flag:: -Mgrace=⟨size⟩ :default: 1M From git at git.haskell.org Mon Jul 24 23:36:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Jul 2017 23:36:27 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Cross-reference more flags (0c04d78) Message-ID: <20170724233627.ED0A83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0c04d7873fc3825b86e44c52e36ab9baca02c959/ghc >--------------------------------------------------------------- commit 0c04d7873fc3825b86e44c52e36ab9baca02c959 Author: Ben Gamari Date: Sun Jul 23 21:09:37 2017 -0400 users-guide: Cross-reference more flags >--------------------------------------------------------------- 0c04d7873fc3825b86e44c52e36ab9baca02c959 docs/users_guide/sooner.rst | 21 +++++++++++---------- 1 file changed, 11 insertions(+), 10 deletions(-) diff --git a/docs/users_guide/sooner.rst b/docs/users_guide/sooner.rst index d6bd2cc..529e062 100644 --- a/docs/users_guide/sooner.rst +++ b/docs/users_guide/sooner.rst @@ -305,9 +305,9 @@ Use unboxed arrays (``UArray``) Use a bigger heap! If your program's GC stats (:rts-flag:`-S [⟨file⟩]` RTS option) indicate that it's doing lots of garbage-collection (say, more than 20% of execution - time), more memory might help — with the ``-H⟨size⟩`` or ``-A⟨size⟩`` RTS + time), more memory might help — with the :rts-flag:`-H⟨size⟩` or :rts-flag:`-A⟨size⟩` RTS options (see :ref:`rts-options-gc`). As a rule of thumb, try setting - ``-H⟨size⟩`` to the amount of memory you're willing to let your process + :rts-flag:`-H ⟨size⟩` to the amount of memory you're willing to let your process consume, or perhaps try passing :ghc-flag:`-H ⟨size⟩` without any argument to let GHC calculate a value based on the amount of live data. @@ -328,11 +328,11 @@ Smaller: producing a program that is smaller single: -funfolding-use-threshold0 option Decrease the "go-for-it" threshold for unfolding smallish expressions. -Give a ``-funfolding-use-threshold0`` option for the extreme case. -(“Only unfoldings with zero cost should proceed.”) Warning: except in -certain specialised cases (like Happy parsers) this is likely to -actually *increase* the size of your program, because unfolding -generally enables extra simplifying optimisations to be performed. +Give a :ghc-flag:`-funfolding-use-threshold=0 <-funfolding-use-threshold=⟨n⟩>` +option for the extreme case. (“Only unfoldings with zero cost should proceed.”) +Warning: except in certain specialised cases (like Happy parsers) this is likely +to actually *increase* the size of your program, because unfolding generally +enables extra simplifying optimisations to be performed. Avoid ``Read``. @@ -350,9 +350,10 @@ Thriftier: producing a program that gobbles less heap space "I think I have a space leak..." -Re-run your program with ``+RTS -S``, and remove all doubt! (You'll see the -heap usage get bigger and bigger...) (Hmmm... this might be even easier with -the ``-G1`` RTS option; so... ``./a.out +RTS -S -G1``) +Re-run your program with :ghc-flag:`+RTS -S <-S [⟨file⟩]>`, and remove all +doubt! (You'll see the heap usage get bigger and bigger...) (Hmmm... this might +be even easier with the :rts-flag:`-G1 <-G ⟨generations⟩>` RTS option; so... +``./a.out +RTS -S -G1``) .. index:: single: -G RTS option From git at git.haskell.org Mon Jul 24 23:36:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Jul 2017 23:36:30 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Eliminate some redundant index entries (58b62d6) Message-ID: <20170724233630.A58A73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/58b62d6b2bffcd31c0f3425330ff738f6ba37271/ghc >--------------------------------------------------------------- commit 58b62d6b2bffcd31c0f3425330ff738f6ba37271 Author: Ben Gamari Date: Sun Jul 23 21:31:47 2017 -0400 users-guide: Eliminate some redundant index entries >--------------------------------------------------------------- 58b62d6b2bffcd31c0f3425330ff738f6ba37271 docs/users_guide/profiling.rst | 6 ------ 1 file changed, 6 deletions(-) diff --git a/docs/users_guide/profiling.rst b/docs/users_guide/profiling.rst index 4107db2..3d25e46 100644 --- a/docs/users_guide/profiling.rst +++ b/docs/users_guide/profiling.rst @@ -347,9 +347,6 @@ for all modules in a program. .. ghc-flag:: -fprof-auto-calls - .. index:: - single: -fprof-auto-calls - Adds an automatic ``SCC`` annotation to all *call sites*. This is particularly useful when using profiling for the purposes of generating stack traces; see the function :base-ref:`traceStack ` in the @@ -373,9 +370,6 @@ for all modules in a program. .. ghc-flag:: -fno-prof-count-entries - .. index:: - single: -fno-prof-count-entries - Tells GHC not to collect information about how often functions are entered at runtime (the "entries" column of the time profile), for this module. This tends to make the profiled code run faster, and From git at git.haskell.org Mon Jul 24 23:36:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Jul 2017 23:36:33 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Make it easier to reference haddocks (3e5d0f1) Message-ID: <20170724233633.81E663A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3e5d0f188d6c8633e55e9ba6c8941c07e459fa4b/ghc >--------------------------------------------------------------- commit 3e5d0f188d6c8633e55e9ba6c8941c07e459fa4b Author: Ben Gamari Date: Mon Jul 24 19:00:24 2017 -0400 users-guide: Make it easier to reference haddocks Previously you had to painstakingly construct the URI to the haddock documentation. Now the Python bits have enough smarts to construct this themselves. Reviewers: austin, patrickdoc Reviewed By: patrickdoc Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3785 >--------------------------------------------------------------- 3e5d0f188d6c8633e55e9ba6c8941c07e459fa4b docs/users_guide/8.2.1-notes.rst | 4 +-- docs/users_guide/conf.py | 41 +++++++++++++++++++++++ docs/users_guide/debug-info.rst | 2 +- docs/users_guide/ffi-chap.rst | 6 ++-- docs/users_guide/ghc_config.py.in | 18 ++++++---- docs/users_guide/ghci.rst | 4 +-- docs/users_guide/glasgow_exts.rst | 62 +++++++++++++++-------------------- docs/users_guide/packages.rst | 8 ++--- docs/users_guide/parallel.rst | 3 +- docs/users_guide/profiling.rst | 6 ++-- docs/users_guide/runtime_control.rst | 6 ++-- docs/users_guide/sooner.rst | 10 +++--- docs/users_guide/using-concurrent.rst | 10 +++--- docs/users_guide/win32-dlls.rst | 3 +- 14 files changed, 108 insertions(+), 75 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 3e5d0f188d6c8633e55e9ba6c8941c07e459fa4b From git at git.haskell.org Mon Jul 24 23:36:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Jul 2017 23:36:36 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Fix URL of deferred type errors paper (897366a) Message-ID: <20170724233636.45EDD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/897366a012de053fd3558ffb665337287c3df926/ghc >--------------------------------------------------------------- commit 897366a012de053fd3558ffb665337287c3df926 Author: Ben Gamari Date: Mon Jul 24 19:01:33 2017 -0400 users-guide: Fix URL of deferred type errors paper Reviewers: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3784 >--------------------------------------------------------------- 897366a012de053fd3558ffb665337287c3df926 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 7096089..a2cc0ba 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -10660,7 +10660,7 @@ ignore the problems in ``a``. For more motivation and details please refer to the :ghc-wiki:`Wiki ` page or the `original -paper `__. +paper `__. Enabling deferring of type errors --------------------------------- From git at git.haskell.org Mon Jul 24 23:36:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Jul 2017 23:36:39 +0000 (UTC) Subject: [commit: ghc] master: DynFlags: Drop rtsBuildTag field (8a8cee7) Message-ID: <20170724233639.06CB93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8a8cee735b80567d2d97b25936ff4da80c7a3b47/ghc >--------------------------------------------------------------- commit 8a8cee735b80567d2d97b25936ff4da80c7a3b47 Author: Ben Gamari Date: Mon Jul 24 19:02:20 2017 -0400 DynFlags: Drop rtsBuildTag field This wasn't used anywhere; the RTS build tag is now constructed in Packages.packageHsLibs. Test Plan: Validate Reviewers: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3768 >--------------------------------------------------------------- 8a8cee735b80567d2d97b25936ff4da80c7a3b47 compiler/main/DynFlags.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 5e33c2e..d25b361 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -750,7 +750,6 @@ data DynFlags = DynFlags { -- ways ways :: [Way], -- ^ Way flags from the command line buildTag :: String, -- ^ The global \"way\" (e.g. \"p\" for prof) - rtsBuildTag :: String, -- ^ The RTS \"way\" -- For object splitting splitInfo :: Maybe (String,Int), @@ -1644,7 +1643,6 @@ defaultDynFlags mySettings = pkgState = emptyPackageState, ways = defaultWays mySettings, buildTag = mkBuildTag (defaultWays mySettings), - rtsBuildTag = mkBuildTag (defaultWays mySettings), splitInfo = Nothing, settings = mySettings, -- ghc -M values @@ -2477,8 +2475,7 @@ updateWays dflags = let theWays = sort $ nub $ ways dflags in dflags { ways = theWays, - buildTag = mkBuildTag (filter (not . wayRTSOnly) theWays), - rtsBuildTag = mkBuildTag theWays + buildTag = mkBuildTag (filter (not . wayRTSOnly) theWays) } -- | Check (and potentially disable) any extensions that aren't allowed From git at git.haskell.org Mon Jul 24 23:36:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Jul 2017 23:36:44 +0000 (UTC) Subject: [commit: ghc] master: ghc-prim: Don't allocate a thunk for each unpacked UTF-8 character (85a295d) Message-ID: <20170724233644.759AC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/85a295d5607b5f8015bb3517601ced0d1adc29ef/ghc >--------------------------------------------------------------- commit 85a295d5607b5f8015bb3517601ced0d1adc29ef Author: Ben Gamari Date: Mon Jul 24 19:01:58 2017 -0400 ghc-prim: Don't allocate a thunk for each unpacked UTF-8 character While debugging #14005 I noticed that unpackCStringUtf8# was allocating a thunk for each Unicode character that it unpacked. This seems hardly worthwhile given that the thunk's closure will be at least three words, whereas the Char itself will be only two and requires only a bit of bit twiddling to construct. Test Plan: Validate Reviewers: simonmar, austin Subscribers: dfeuer, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3769 >--------------------------------------------------------------- 85a295d5607b5f8015bb3517601ced0d1adc29ef libraries/ghc-prim/GHC/CString.hs | 28 ++++++++++++++++------------ 1 file changed, 16 insertions(+), 12 deletions(-) diff --git a/libraries/ghc-prim/GHC/CString.hs b/libraries/ghc-prim/GHC/CString.hs index cdda2db..0e6199f 100644 --- a/libraries/ghc-prim/GHC/CString.hs +++ b/libraries/ghc-prim/GHC/CString.hs @@ -125,24 +125,28 @@ unpackCStringUtf8# :: Addr# -> [Char] unpackCStringUtf8# addr = unpack 0# where + -- We take care to strictly evaluate the character decoding as + -- indexCharOffAddr# is marked with the can_fail flag and + -- consequently GHC won't evaluate the expression unless it is absolutely + -- needed. unpack nh | isTrue# (ch `eqChar#` '\0'# ) = [] | isTrue# (ch `leChar#` '\x7F'#) = C# ch : unpack (nh +# 1#) | isTrue# (ch `leChar#` '\xDF'#) = - C# (chr# (((ord# ch -# 0xC0#) `uncheckedIShiftL#` 6#) +# - (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#))) : - unpack (nh +# 2#) + let !c = C# (chr# (((ord# ch -# 0xC0#) `uncheckedIShiftL#` 6#) +# + (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#))) + in c : unpack (nh +# 2#) | isTrue# (ch `leChar#` '\xEF'#) = - C# (chr# (((ord# ch -# 0xE0#) `uncheckedIShiftL#` 12#) +# - ((ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#` 6#) +# - (ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#))) : - unpack (nh +# 3#) + let !c = C# (chr# (((ord# ch -# 0xE0#) `uncheckedIShiftL#` 12#) +# + ((ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#` 6#) +# + (ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#))) + in c : unpack (nh +# 3#) | True = - C# (chr# (((ord# ch -# 0xF0#) `uncheckedIShiftL#` 18#) +# - ((ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#` 12#) +# - ((ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#) `uncheckedIShiftL#` 6#) +# - (ord# (indexCharOffAddr# addr (nh +# 3#)) -# 0x80#))) : - unpack (nh +# 4#) + let !c = C# (chr# (((ord# ch -# 0xF0#) `uncheckedIShiftL#` 18#) +# + ((ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#` 12#) +# + ((ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#) `uncheckedIShiftL#` 6#) +# + (ord# (indexCharOffAddr# addr (nh +# 3#)) -# 0x80#))) + in c : unpack (nh +# 4#) where !ch = indexCharOffAddr# addr nh From git at git.haskell.org Mon Jul 24 23:36:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Jul 2017 23:36:41 +0000 (UTC) Subject: [commit: ghc] master: Use libpthread instead of libthr on FreeBSD (d8051c6) Message-ID: <20170724233641.BC07B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d8051c6cf08f02331f98fed7d5e88a95bd76e534/ghc >--------------------------------------------------------------- commit d8051c6cf08f02331f98fed7d5e88a95bd76e534 Author: Ben Gamari Date: Mon Jul 24 19:02:56 2017 -0400 Use libpthread instead of libthr on FreeBSD Since #847 we have used libthr due to reported hangs with FreeBSD's KSE-based M:N pthread implementation. However, this was nearly 12 years ago and today libpthread seems to work fine. Moreover, adding -lthr to the linker flags break when used in conjunction with -r when gold is used (since -l and -r are incompatible although BFD ld doesn't complain). Test Plan: Validate on FreeBSD Reviewers: kgardas, austin Subscribers: rwbarton, thomie GHC Trac Issues: #847 Differential Revision: https://phabricator.haskell.org/D3773 >--------------------------------------------------------------- d8051c6cf08f02331f98fed7d5e88a95bd76e534 compiler/main/DynFlags.hs | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index d25b361..cc9bbb8 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -1446,11 +1446,7 @@ wayOptl :: Platform -> Way -> [String] wayOptl _ (WayCustom {}) = [] wayOptl platform WayThreaded = case platformOS platform of - -- FreeBSD's default threading library is the KSE-based M:N libpthread, - -- which GHC has some problems with. It's currently not clear whether - -- the problems are our fault or theirs, but it seems that using the - -- alternative 1:1 threading library libthr works around it: - OSFreeBSD -> ["-lthr"] + OSFreeBSD -> ["-pthread"] OSOpenBSD -> ["-pthread"] OSNetBSD -> ["-pthread"] _ -> [] From git at git.haskell.org Tue Jul 25 01:07:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 01:07:01 +0000 (UTC) Subject: [commit: ghc] master: base: Introduce GHC.ByteOrder (58545fd) Message-ID: <20170725010701.0290F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/58545fde018460a2e9d05a8659951acfb277209f/ghc >--------------------------------------------------------------- commit 58545fde018460a2e9d05a8659951acfb277209f Author: Ben Gamari Date: Mon Jul 24 19:54:37 2017 -0400 base: Introduce GHC.ByteOrder This provides a ByteOrder type as well as a targetByteOrder value, which indicates the byte ordering used by the target machine. We might also consider exposing this via Data.Bits if the CLC is so inclined. Test Plan: Needs test Reviewers: hvr, RyanGlScott, austin Reviewed By: hvr, RyanGlScott Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3786 >--------------------------------------------------------------- 58545fde018460a2e9d05a8659951acfb277209f libraries/base/GHC/ByteOrder.hs | 31 +++++++++++++++++++++++++++++++ libraries/base/base.cabal | 1 + 2 files changed, 32 insertions(+) diff --git a/libraries/base/GHC/ByteOrder.hs b/libraries/base/GHC/ByteOrder.hs new file mode 100644 index 0000000..eecc56c --- /dev/null +++ b/libraries/base/GHC/ByteOrder.hs @@ -0,0 +1,31 @@ +{-# LANGUAGE CPP #-} + +----------------------------------------------------------------------------- +-- | +-- Module : GHC.ByteOrder +-- Copyright : (c) The University of Glasgow, 1994-2000 +-- License : see libraries/base/LICENSE +-- +-- Maintainer : cvs-ghc at haskell.org +-- Stability : internal +-- Portability : non-portable (GHC extensions) +-- +-- Target byte ordering. +-- +----------------------------------------------------------------------------- + +module GHC.ByteOrder where + +-- | Byte ordering. +data ByteOrder + = BigEndian -- ^ most-significant-byte occurs in lowest address. + | LittleEndian -- ^ least-significant-byte occurs in lowest address. + deriving (Eq, Ord, Bounded, Enum, Read, Show) + +-- | The byte ordering of the target machine. +targetByteOrder :: ByteOrder +#if defined(WORDS_BIGENDIAN) +targetByteOrder = BigEndian +#else +targetByteOrder = LittleEndian +#endif diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal index f00fb87..9429de0 100644 --- a/libraries/base/base.cabal +++ b/libraries/base/base.cabal @@ -202,6 +202,7 @@ Library Foreign.Storable GHC.Arr GHC.Base + GHC.ByteOrder GHC.Char GHC.Conc GHC.Conc.IO From git at git.haskell.org Tue Jul 25 01:07:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 01:07:03 +0000 (UTC) Subject: [commit: ghc] master: Fix import error with -XPackageImports when the module has a duplicate name (2183ac1) Message-ID: <20170725010703.BF5463A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2183ac16a98146bb673b5530ca154499a1c6166e/ghc >--------------------------------------------------------------- commit 2183ac16a98146bb673b5530ca154499a1c6166e Author: Eugene Akentyev Date: Mon Jul 24 19:53:57 2017 -0400 Fix import error with -XPackageImports when the module has a duplicate name Reviewers: austin, bgamari, mpickering Reviewed By: bgamari Subscribers: mpickering, rwbarton, thomie GHC Trac Issues: #13168 Differential Revision: https://phabricator.haskell.org/D3738 >--------------------------------------------------------------- 2183ac16a98146bb673b5530ca154499a1c6166e compiler/typecheck/TcRnDriver.hs | 13 +++++++++---- testsuite/tests/typecheck/T13168/all.T | 2 +- 2 files changed, 10 insertions(+), 5 deletions(-) diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index c9c259e..8a6d72e 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -1777,14 +1777,19 @@ runTcInteractive hsc_env thing_inside vcat (map ppr [ local_gres | gres <- occEnvElts (ic_rn_gbl_env icxt) , let local_gres = filter isLocalGRE gres , not (null local_gres) ]) ] - ; let getOrphans m = fmap (\iface -> mi_module iface + + ; let getOrphans m mb_pkg = fmap (\iface -> mi_module iface : dep_orphs (mi_deps iface)) (loadSrcInterface (text "runTcInteractive") m - False Nothing) + False mb_pkg) + ; orphs <- fmap concat . forM (ic_imports icxt) $ \i -> case i of - IIModule n -> getOrphans n - IIDecl i -> getOrphans (unLoc (ideclName i)) + IIModule n -> getOrphans n Nothing + IIDecl i -> + let mb_pkg = sl_fs <$> ideclPkgQual i in + getOrphans (unLoc (ideclName i)) mb_pkg + ; let imports = emptyImportAvails { imp_orphs = orphs } diff --git a/testsuite/tests/typecheck/T13168/all.T b/testsuite/tests/typecheck/T13168/all.T index 8552366..43a5e1b 100644 --- a/testsuite/tests/typecheck/T13168/all.T +++ b/testsuite/tests/typecheck/T13168/all.T @@ -1,4 +1,4 @@ test('T13168', - [extra_files(['package1', 'package2', 'Setup.hs']), expect_broken(13168)], + extra_files(['package1', 'package2', 'Setup.hs']), run_command, ['$MAKE -s --no-print-directory T13168']) From git at git.haskell.org Tue Jul 25 01:06:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 01:06:57 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add testcase for #13168 (8ec7770) Message-ID: <20170725010657.D843B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8ec7770886a23da86e59ddfa112dcc6b050d088c/ghc >--------------------------------------------------------------- commit 8ec7770886a23da86e59ddfa112dcc6b050d088c Author: Ben Gamari Date: Sun Jul 23 13:15:22 2017 -0400 testsuite: Add testcase for #13168 Thanks to Ryan Scott for the testcase. Currently broken. >--------------------------------------------------------------- 8ec7770886a23da86e59ddfa112dcc6b050d088c testsuite/tests/typecheck/T13168/Makefile | 19 +++++++++++++++++++ .../cabal/bkpcabal01 => typecheck/T13168}/Setup.hs | 0 testsuite/tests/typecheck/T13168/T13168.script | 3 +++ testsuite/tests/typecheck/T13168/T13168.stderr | 4 ++++ testsuite/tests/typecheck/T13168/T13168.stdout | 1 + testsuite/tests/typecheck/T13168/all.T | 4 ++++ .../typecheck/T13168/package1/DuplicateModuleName.hs | 3 +++ .../tests/typecheck/T13168/package1/package1.cabal | 11 +++++++++++ .../typecheck/T13168/package2/DuplicateModuleName.hs | 3 +++ .../tests/typecheck/T13168/package2/package2.cabal | 12 ++++++++++++ 10 files changed, 60 insertions(+) diff --git a/testsuite/tests/typecheck/T13168/Makefile b/testsuite/tests/typecheck/T13168/Makefile new file mode 100644 index 0000000..4dc9d7b --- /dev/null +++ b/testsuite/tests/typecheck/T13168/Makefile @@ -0,0 +1,19 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +SETUP=../Setup -v0 +CONFIGURE=$(SETUP) configure --with-ghc='$(TEST_HC)' --ghc-options='$(TEST_HC_OPTS)' --package-db='$(PWD)/tmp.d' --prefix='$(PWD)/inst' + +T13168: clean + $(MAKE) -s --no-print-directory clean + '$(GHC_PKG)' init tmp.d + '$(TEST_HC)' -v0 --make Setup + + cd package1 && $(CONFIGURE) && $(SETUP) build && $(SETUP) copy && $(SETUP) register + cd package2 && $(CONFIGURE) && $(SETUP) build && $(SETUP) copy && $(SETUP) register + + '$(TEST_HC)' $(TEST_HC_OPTS_INTERACTIVE) -package-db tmp.d < T13168.script + +clean : + $(RM) -r tmp.d inst dist Setup$(exeext) diff --git a/testsuite/tests/backpack/cabal/bkpcabal01/Setup.hs b/testsuite/tests/typecheck/T13168/Setup.hs similarity index 100% copy from testsuite/tests/backpack/cabal/bkpcabal01/Setup.hs copy to testsuite/tests/typecheck/T13168/Setup.hs diff --git a/testsuite/tests/typecheck/T13168/T13168.script b/testsuite/tests/typecheck/T13168/T13168.script new file mode 100644 index 0000000..6fa3215 --- /dev/null +++ b/testsuite/tests/typecheck/T13168/T13168.script @@ -0,0 +1,3 @@ +:set -XPackageImports +import "package1" DuplicateModuleName +Window diff --git a/testsuite/tests/typecheck/T13168/T13168.stderr b/testsuite/tests/typecheck/T13168/T13168.stderr new file mode 100644 index 0000000..e69dbaa --- /dev/null +++ b/testsuite/tests/typecheck/T13168/T13168.stderr @@ -0,0 +1,4 @@ +Warning: -rtsopts and -with-rtsopts have no effect with -shared. + Call hs_init_ghc() from your main() function to set these options. +Warning: -rtsopts and -with-rtsopts have no effect with -shared. + Call hs_init_ghc() from your main() function to set these options. diff --git a/testsuite/tests/typecheck/T13168/T13168.stdout b/testsuite/tests/typecheck/T13168/T13168.stdout new file mode 100644 index 0000000..a935d2f --- /dev/null +++ b/testsuite/tests/typecheck/T13168/T13168.stdout @@ -0,0 +1 @@ +Window diff --git a/testsuite/tests/typecheck/T13168/all.T b/testsuite/tests/typecheck/T13168/all.T new file mode 100644 index 0000000..8552366 --- /dev/null +++ b/testsuite/tests/typecheck/T13168/all.T @@ -0,0 +1,4 @@ +test('T13168', + [extra_files(['package1', 'package2', 'Setup.hs']), expect_broken(13168)], + run_command, + ['$MAKE -s --no-print-directory T13168']) diff --git a/testsuite/tests/typecheck/T13168/package1/DuplicateModuleName.hs b/testsuite/tests/typecheck/T13168/package1/DuplicateModuleName.hs new file mode 100644 index 0000000..84a32b2 --- /dev/null +++ b/testsuite/tests/typecheck/T13168/package1/DuplicateModuleName.hs @@ -0,0 +1,3 @@ +module DuplicateModuleName (Window(..)) where + +data Window = Window deriving (Show) diff --git a/testsuite/tests/typecheck/T13168/package1/package1.cabal b/testsuite/tests/typecheck/T13168/package1/package1.cabal new file mode 100644 index 0000000..543fc10 --- /dev/null +++ b/testsuite/tests/typecheck/T13168/package1/package1.cabal @@ -0,0 +1,11 @@ +name: package1 +version: 0.1.0.0 +license: BSD3 +build-type: Simple +cabal-version: >=1.10 + +library + exposed-modules: DuplicateModuleName + build-depends: base >= 4.3 && < 5 + default-language: Haskell2010 + ghc-options: -Wall diff --git a/testsuite/tests/typecheck/T13168/package2/DuplicateModuleName.hs b/testsuite/tests/typecheck/T13168/package2/DuplicateModuleName.hs new file mode 100644 index 0000000..91c65b5 --- /dev/null +++ b/testsuite/tests/typecheck/T13168/package2/DuplicateModuleName.hs @@ -0,0 +1,3 @@ +module DuplicateModuleName (Window(..)) where + +data Window = Window diff --git a/testsuite/tests/typecheck/T13168/package2/package2.cabal b/testsuite/tests/typecheck/T13168/package2/package2.cabal new file mode 100644 index 0000000..ea40c9d --- /dev/null +++ b/testsuite/tests/typecheck/T13168/package2/package2.cabal @@ -0,0 +1,12 @@ +name: package2 +version: 0.1.0.0 +license: BSD3 +build-type: Simple +cabal-version: >=1.10 + +library + exposed-modules: DuplicateModuleName + build-depends: base >= 4.3 && < 5 + default-language: Haskell2010 + ghc-options: -Wall + From git at git.haskell.org Tue Jul 25 15:24:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 15:24:15 +0000 (UTC) Subject: [commit: ghc] master: Expose FrontendPluginAction (104c72b) Message-ID: <20170725152415.21B7F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/104c72b38eea3622f050323404b0f827ee2ec53a/ghc >--------------------------------------------------------------- commit 104c72b38eea3622f050323404b0f827ee2ec53a Author: Matthew Pickering Date: Tue Jul 25 16:22:39 2017 +0100 Expose FrontendPluginAction It is mentioned in the API but not exported. >--------------------------------------------------------------- 104c72b38eea3622f050323404b0f827ee2ec53a compiler/main/Plugins.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/main/Plugins.hs b/compiler/main/Plugins.hs index 74403ed..273bf7a 100644 --- a/compiler/main/Plugins.hs +++ b/compiler/main/Plugins.hs @@ -1,5 +1,5 @@ module Plugins ( - FrontendPlugin(..), defaultFrontendPlugin, + FrontendPlugin(..), defaultFrontendPlugin, FrontendPluginAction, Plugin(..), CommandLineOption, defaultPlugin ) where From git at git.haskell.org Tue Jul 25 15:24:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 15:24:17 +0000 (UTC) Subject: [commit: ghc] master: Remove unused language pragma (7d1909a) Message-ID: <20170725152417.D17D83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7d1909ad110f05c8cb2fb0689ee75857ceb945f6/ghc >--------------------------------------------------------------- commit 7d1909ad110f05c8cb2fb0689ee75857ceb945f6 Author: Matthew Pickering Date: Tue Jul 25 16:23:31 2017 +0100 Remove unused language pragma >--------------------------------------------------------------- 7d1909ad110f05c8cb2fb0689ee75857ceb945f6 compiler/utils/Outputable.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/utils/Outputable.hs b/compiler/utils/Outputable.hs index 4107e5b..be5930e 100644 --- a/compiler/utils/Outputable.hs +++ b/compiler/utils/Outputable.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, ImplicitParams #-} +{-# LANGUAGE CPP #-} {- (c) The University of Glasgow 2006-2012 (c) The GRASP Project, Glasgow University, 1992-1998 From git at git.haskell.org Tue Jul 25 16:08:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 16:08:46 +0000 (UTC) Subject: [commit: ghc] master: Revert "Remove unused language pragma" (36b270a) Message-ID: <20170725160846.E83DA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/36b270a94e689220c77ab49a863435dda6b60621/ghc >--------------------------------------------------------------- commit 36b270a94e689220c77ab49a863435dda6b60621 Author: Matthew Pickering Date: Tue Jul 25 17:08:15 2017 +0100 Revert "Remove unused language pragma" This reverts commit 7d1909ad110f05c8cb2fb0689ee75857ceb945f6. It is actually used for Callstacks, woops! >--------------------------------------------------------------- 36b270a94e689220c77ab49a863435dda6b60621 compiler/utils/Outputable.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/utils/Outputable.hs b/compiler/utils/Outputable.hs index be5930e..4107e5b 100644 --- a/compiler/utils/Outputable.hs +++ b/compiler/utils/Outputable.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP #-} +{-# LANGUAGE CPP, ImplicitParams #-} {- (c) The University of Glasgow 2006-2012 (c) The GRASP Project, Glasgow University, 1992-1998 From git at git.haskell.org Tue Jul 25 16:32:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 16:32:51 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T13904' created Message-ID: <20170725163251.862653A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T13904 Referencing: baea1d6ef1997db3194f0cd9226758e28e7d6312 From git at git.haskell.org Tue Jul 25 16:32:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 16:32:54 +0000 (UTC) Subject: [commit: ghc] wip/T13904: fix for #13904: LLVM trashing caller-save global vars (baea1d6) Message-ID: <20170725163254.467383A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T13904 Link : http://ghc.haskell.org/trac/ghc/changeset/baea1d6ef1997db3194f0cd9226758e28e7d6312/ghc >--------------------------------------------------------------- commit baea1d6ef1997db3194f0cd9226758e28e7d6312 Author: Kavon Farvardin Date: Fri Jun 30 16:14:25 2017 +0100 fix for #13904: LLVM trashing caller-save global vars >--------------------------------------------------------------- baea1d6ef1997db3194f0cd9226758e28e7d6312 compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 40 ++------------------------------- 1 file changed, 2 insertions(+), 38 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index f6ff838..a4f67fa 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -12,7 +12,7 @@ import LlvmCodeGen.Base import LlvmCodeGen.Regs import BlockId -import CodeGen.Platform ( activeStgRegs, callerSaves ) +import CodeGen.Platform ( activeStgRegs ) import CLabel import Cmm import PprCmm @@ -209,7 +209,6 @@ genCall t@(PrimTarget (MO_Prefetch_Data localityInt)) [] args fptr <- liftExprData $ getFunPtr funTy t argVars' <- castVarsW $ zip argVars argTy - doTrashStmts let argSuffix = [mkIntLit i32 0, mkIntLit i32 localityInt, mkIntLit i32 1] statement $ Expr $ Call StdCall fptr (argVars' ++ argSuffix) [] | otherwise = panic $ "prefetch locality level integer must be between 0 and 3, given: " ++ (show localityInt) @@ -287,7 +286,6 @@ genCall t@(PrimTarget op) [] args fptr <- getFunPtrW funTy t argVars' <- castVarsW $ zip argVars argTy - doTrashStmts let alignVal = mkIntLit i32 align arguments = argVars' ++ (alignVal:isVolVal) statement $ Expr $ Call StdCall fptr arguments [] @@ -439,7 +437,6 @@ genCall target res args = runStmtsDecls $ do | never_returns = statement $ Unreachable | otherwise = return () - doTrashStmts -- make the actual call case retTy of @@ -1697,12 +1694,9 @@ genLit _ CmmHighStackMark funPrologue :: LiveGlobalRegs -> [CmmBlock] -> LlvmM StmtData funPrologue live cmmBlocks = do - trash <- getTrashRegs let getAssignedRegs :: CmmNode O O -> [CmmReg] getAssignedRegs (CmmAssign reg _) = [reg] - -- Calls will trash all registers. Unfortunately, this needs them to - -- be stack-allocated in the first place. - getAssignedRegs (CmmUnsafeForeignCall _ rs _) = map CmmGlobal trash ++ map CmmLocal rs + getAssignedRegs (CmmUnsafeForeignCall _ rs _) = map CmmLocal rs getAssignedRegs _ = [] getRegsBlock (_, body, _) = concatMap getAssignedRegs $ blockToList body assignedRegs = nub $ concatMap (getRegsBlock . blockSplit) cmmBlocks @@ -1759,31 +1753,6 @@ funEpilogue live = do let (vars, stmts) = unzip loads return (catMaybes vars, concatOL stmts) - --- | A series of statements to trash all the STG registers. --- --- In LLVM we pass the STG registers around everywhere in function calls. --- So this means LLVM considers them live across the entire function, when --- in reality they usually aren't. For Caller save registers across C calls --- the saving and restoring of them is done by the Cmm code generator, --- using Cmm local vars. So to stop LLVM saving them as well (and saving --- all of them since it thinks they're always live, we trash them just --- before the call by assigning the 'undef' value to them. The ones we --- need are restored from the Cmm local var and the ones we don't need --- are fine to be trashed. -getTrashStmts :: LlvmM LlvmStatements -getTrashStmts = do - regs <- getTrashRegs - stmts <- flip mapM regs $ \ r -> do - reg <- getCmmReg (CmmGlobal r) - let ty = (pLower . getVarType) reg - return $ Store (LMLitVar $ LMUndefLit ty) reg - return $ toOL stmts - -getTrashRegs :: LlvmM [GlobalReg] -getTrashRegs = do plat <- getLlvmPlatform - return $ filter (callerSaves plat) (activeStgRegs plat) - -- | Get a function pointer to the CLabel specified. -- -- This is for Haskell functions, function type is assumed, so doesn't work @@ -1907,8 +1876,3 @@ getCmmRegW = lift . getCmmReg genLoadW :: Atomic -> CmmExpr -> CmmType -> WriterT LlvmAccum LlvmM LlvmVar genLoadW atomic e ty = liftExprData $ genLoad atomic e ty - -doTrashStmts :: WriterT LlvmAccum LlvmM () -doTrashStmts = do - stmts <- lift getTrashStmts - tell $ LlvmAccum stmts mempty From git at git.haskell.org Tue Jul 25 17:53:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 17:53:49 +0000 (UTC) Subject: [commit: ghc] branch 'wip/annotate-core' created Message-ID: <20170725175349.2F3803A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/annotate-core Referencing: 8b50cd4721f87a3d37254494d56d0388fd4c9b5f From git at git.haskell.org Tue Jul 25 17:53:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 17:53:51 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: Add text dependency (5d0551b) Message-ID: <20170725175351.E732F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/5d0551be7c8b4106e67938d9958bac20abd657c0/ghc >--------------------------------------------------------------- commit 5d0551be7c8b4106e67938d9958bac20abd657c0 Author: Ben Gamari Date: Thu Jun 22 11:59:32 2017 -0400 Add text dependency >--------------------------------------------------------------- 5d0551be7c8b4106e67938d9958bac20abd657c0 .gitmodules | 4 ++++ compiler/ghc.cabal.in | 1 + compiler/main/HscMain.hs | 1 + ghc.mk | 3 ++- ghc/Main.hs | 1 + ghc/ghc-bin.cabal.in | 1 + libraries/text | 1 + packages | 1 + 8 files changed, 12 insertions(+), 1 deletion(-) diff --git a/.gitmodules b/.gitmodules index 55d360a..5a2e8e0 100644 --- a/.gitmodules +++ b/.gitmodules @@ -6,6 +6,10 @@ path = libraries/bytestring url = ../packages/bytestring.git ignore = untracked +[submodule "libraries/text"] + path = libraries/text + url = https://github.com/bollu/text.git + ignore = untracked [submodule "libraries/Cabal"] path = libraries/Cabal url = ../packages/Cabal.git diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index f40c8ba..aff9ee4 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -62,6 +62,7 @@ Library template-haskell == 2.12.*, hpc == 0.6.*, transformers == 0.5.*, + text == 1.2.*, ghc-boot == @ProjectVersionMunged@, ghc-boot-th == @ProjectVersionMunged@, ghci == @ProjectVersionMunged@ diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index c514e5b..0f99909 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -166,6 +166,7 @@ import qualified Data.Map as Map import qualified Data.Set as S import Data.Set (Set) +import qualified Data.Text as DontUseText #include "HsVersions.h" diff --git a/ghc.mk b/ghc.mk index 4eb1658..3aae89b 100644 --- a/ghc.mk +++ b/ghc.mk @@ -430,7 +430,7 @@ else # CLEANING # programs such as GHC and ghc-pkg, that we do not assume the stage0 # compiler already has installed (or up-to-date enough). -PACKAGES_STAGE0 = binary Cabal/Cabal hpc ghc-boot-th ghc-boot transformers template-haskell ghci +PACKAGES_STAGE0 = binary Cabal/Cabal hpc ghc-boot-th ghc-boot transformers template-haskell ghci text ifeq "$(Windows_Host)" "NO" PACKAGES_STAGE0 += terminfo endif @@ -463,6 +463,7 @@ PACKAGES_STAGE1 += ghc-boot PACKAGES_STAGE1 += template-haskell PACKAGES_STAGE1 += transformers PACKAGES_STAGE1 += ghc-compact +PACKAGES_STAGE1 += text ifeq "$(HADDOCK_DOCS)" "YES" PACKAGES_STAGE1 += xhtml diff --git a/ghc/Main.hs b/ghc/Main.hs index a75aba3..ef05846 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -73,6 +73,7 @@ import Control.Monad import Data.Char import Data.List import Data.Maybe +import qualified Data.Text as DontUseText ----------------------------------------------------------------------------- -- ToDo: diff --git a/ghc/ghc-bin.cabal.in b/ghc/ghc-bin.cabal.in index b04c13a..011cf4a 100644 --- a/ghc/ghc-bin.cabal.in +++ b/ghc/ghc-bin.cabal.in @@ -34,6 +34,7 @@ Executable ghc directory >= 1 && < 1.4, process >= 1 && < 1.7, filepath >= 1 && < 1.5, + text == 1.2.*, ghc-boot == @ProjectVersionMunged@, ghc == @ProjectVersionMunged@ diff --git a/libraries/text b/libraries/text new file mode 160000 index 0000000..f127122 --- /dev/null +++ b/libraries/text @@ -0,0 +1 @@ +Subproject commit f12712241987d5b8f0ebb1bdcd64edfc26ea582e diff --git a/packages b/packages index 6ee8071..054626a 100644 --- a/packages +++ b/packages @@ -55,6 +55,7 @@ libraries/hpc - - - libraries/pretty - - https://github.com/haskell/pretty.git libraries/process - - ssh://git at github.com/haskell/process.git libraries/terminfo - - https://github.com/judah/terminfo.git +libraries/text - - https://github.com/bollu/text libraries/time - - https://github.com/haskell/time.git libraries/transformers - - https://git.haskell.org/darcs-mirrors/transformers.git libraries/unix - - ssh://git at github.com/haskell/unix.git From git at git.haskell.org Tue Jul 25 17:53:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 17:53:57 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: Use prettyprinter (fa32633) Message-ID: <20170725175357.70FB13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/fa32633f2abc9b69145783eb473f7c785c39c1b9/ghc >--------------------------------------------------------------- commit fa32633f2abc9b69145783eb473f7c785c39c1b9 Author: Ben Gamari Date: Sat Jun 24 10:05:38 2017 -0400 Use prettyprinter >--------------------------------------------------------------- fa32633f2abc9b69145783eb473f7c785c39c1b9 compiler/llvmGen/LlvmCodeGen.hs | 4 +- compiler/llvmGen/LlvmCodeGen/Base.hs | 6 +- compiler/main/HscMain.hs | 2 + compiler/nativeGen/AsmCodeGen.hs | 23 ++--- compiler/utils/Outputable.hs | 18 ++-- compiler/utils/Pretty.hs | 185 ++++++++++++++++++++++++++++++++--- ghc/Main.hs | 1 + 7 files changed, 203 insertions(+), 36 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fa32633f2abc9b69145783eb473f7c785c39c1b9 From git at git.haskell.org Tue Jul 25 17:53:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 17:53:54 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: Add pretty-printer dependency (f3de97f) Message-ID: <20170725175354.AA3153A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/f3de97f67bbcf5edbcb56c9b4b8d593ea8d1c139/ghc >--------------------------------------------------------------- commit f3de97f67bbcf5edbcb56c9b4b8d593ea8d1c139 Author: Ben Gamari Date: Sat Jun 24 10:05:14 2017 -0400 Add pretty-printer dependency >--------------------------------------------------------------- f3de97f67bbcf5edbcb56c9b4b8d593ea8d1c139 .gitmodules | 3 +++ compiler/ghc.cabal.in | 1 + ghc.mk | 3 ++- ghc/ghc-bin.cabal.in | 1 + libraries/prettyprinter-core | 1 + packages | 1 + 6 files changed, 9 insertions(+), 1 deletion(-) diff --git a/.gitmodules b/.gitmodules index 5a2e8e0..05ca581 100644 --- a/.gitmodules +++ b/.gitmodules @@ -125,3 +125,6 @@ [submodule ".arc-linters/arcanist-external-json-linter"] path = .arc-linters/arcanist-external-json-linter url = ../arcanist-external-json-linter.git +[submodule "libraries/prettyprinter-core"] + path = libraries/prettyprinter-core + url = https://github.com/bollu/prettyprinter-core.git diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index aff9ee4..4f2db5e 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -63,6 +63,7 @@ Library hpc == 0.6.*, transformers == 0.5.*, text == 1.2.*, + prettyprinter == 1.1.*, ghc-boot == @ProjectVersionMunged@, ghc-boot-th == @ProjectVersionMunged@, ghci == @ProjectVersionMunged@ diff --git a/ghc.mk b/ghc.mk index 3aae89b..da6e4b9 100644 --- a/ghc.mk +++ b/ghc.mk @@ -430,7 +430,7 @@ else # CLEANING # programs such as GHC and ghc-pkg, that we do not assume the stage0 # compiler already has installed (or up-to-date enough). -PACKAGES_STAGE0 = binary Cabal/Cabal hpc ghc-boot-th ghc-boot transformers template-haskell ghci text +PACKAGES_STAGE0 = binary Cabal/Cabal hpc ghc-boot-th ghc-boot transformers template-haskell ghci text prettyprinter-core ifeq "$(Windows_Host)" "NO" PACKAGES_STAGE0 += terminfo endif @@ -464,6 +464,7 @@ PACKAGES_STAGE1 += template-haskell PACKAGES_STAGE1 += transformers PACKAGES_STAGE1 += ghc-compact PACKAGES_STAGE1 += text +PACKAGES_STAGE1 += prettyprinter-core ifeq "$(HADDOCK_DOCS)" "YES" PACKAGES_STAGE1 += xhtml diff --git a/ghc/ghc-bin.cabal.in b/ghc/ghc-bin.cabal.in index 011cf4a..74793bc 100644 --- a/ghc/ghc-bin.cabal.in +++ b/ghc/ghc-bin.cabal.in @@ -35,6 +35,7 @@ Executable ghc process >= 1 && < 1.7, filepath >= 1 && < 1.5, text == 1.2.*, + prettyprinter == 1.1.*, ghc-boot == @ProjectVersionMunged@, ghc == @ProjectVersionMunged@ diff --git a/libraries/prettyprinter-core b/libraries/prettyprinter-core new file mode 160000 index 0000000..8697cc9 --- /dev/null +++ b/libraries/prettyprinter-core @@ -0,0 +1 @@ +Subproject commit 8697cc9cfe6937d6479396a96c600a4b6d556ab5 diff --git a/packages b/packages index 054626a..ea02b73 100644 --- a/packages +++ b/packages @@ -41,6 +41,7 @@ ghc-tarballs windows ghc-tarballs.git - libffi-tarballs - - - utils/hsc2hs - - - utils/haddock - - ssh://git at github.com/haskell/haddock.git +libraries/prettyprinter-core - - https://github.com/bollu/prettyprinter-core.git libraries/array - - - libraries/binary - - https://github.com/kolmodin/binary.git libraries/bytestring - - https://github.com/haskell/bytestring.git From git at git.haskell.org Tue Jul 25 17:54:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 17:54:00 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: Fix errant newlines (34edba0) Message-ID: <20170725175400.2D67C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/34edba0e312cb736b26370536f65fb49d9b51b5e/ghc >--------------------------------------------------------------- commit 34edba0e312cb736b26370536f65fb49d9b51b5e Author: Ben Gamari Date: Sat Jun 24 12:40:35 2017 -0400 Fix errant newlines >--------------------------------------------------------------- 34edba0e312cb736b26370536f65fb49d9b51b5e compiler/utils/Pretty.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/utils/Pretty.hs b/compiler/utils/Pretty.hs index 15b8c64..0f6ca4b 100644 --- a/compiler/utils/Pretty.hs +++ b/compiler/utils/Pretty.hs @@ -123,6 +123,7 @@ import GHC.Ptr ( Ptr(..) ) import qualified Data.Text as T import qualified Data.Text.Lazy as TL +import qualified Data.Text.Lazy.IO as TL import Data.Text.Prettyprint.Doc -- PI = PrettyprinterInternal @@ -1010,7 +1011,7 @@ printDoc :: Mode -> Int -> Handle -> Doc a -> IO () printDoc mode cols hdl doc = printDoc_ mode cols hdl (doc <> hardline) printDoc_ :: Mode -> Int -> Handle -> Doc a -> IO () -printDoc_ mode pprCols hdl doc = renderIO hdl (layoutPretty (mkLayoutOptions mode pprCols) doc) where +printDoc_ mode pprCols hdl doc = TL.hPutStr hdl (renderLazy $ layoutPretty (mkLayoutOptions mode pprCols) doc) where mkLayoutOptions :: Mode -> Int -> LayoutOptions -- Note that this should technically be 1.5 as per the old implementation. -- I have no idea why that is. From git at git.haskell.org Tue Jul 25 17:54:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 17:54:02 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: Try something (63ccd40) Message-ID: <20170725175402.E79043A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/63ccd40224a727065a4497d3d96f0ab783236c1a/ghc >--------------------------------------------------------------- commit 63ccd40224a727065a4497d3d96f0ab783236c1a Author: Ben Gamari Date: Sat Jun 24 13:01:37 2017 -0400 Try something >--------------------------------------------------------------- 63ccd40224a727065a4497d3d96f0ab783236c1a compiler/utils/Pretty.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/utils/Pretty.hs b/compiler/utils/Pretty.hs index 0f6ca4b..a7969e6 100644 --- a/compiler/utils/Pretty.hs +++ b/compiler/utils/Pretty.hs @@ -1008,10 +1008,10 @@ renderStyle s d = TL.unpack $ renderLazy (layoutPretty (styleToLayoutOptions s) printDoc :: Mode -> Int -> Handle -> Doc a -> IO () -- printDoc adds a newline to the end -printDoc mode cols hdl doc = printDoc_ mode cols hdl (doc <> hardline) +printDoc mode cols hdl doc = printDoc_ mode cols hdl (doc) printDoc_ :: Mode -> Int -> Handle -> Doc a -> IO () -printDoc_ mode pprCols hdl doc = TL.hPutStr hdl (renderLazy $ layoutPretty (mkLayoutOptions mode pprCols) doc) where +printDoc_ mode pprCols hdl doc = TL.hPutStrLn hdl (renderLazy $ layoutPretty (mkLayoutOptions mode pprCols) doc) where mkLayoutOptions :: Mode -> Int -> LayoutOptions -- Note that this should technically be 1.5 as per the old implementation. -- I have no idea why that is. From git at git.haskell.org Tue Jul 25 17:54:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 17:54:05 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: Debugging ghc-pkg (8ea1835) Message-ID: <20170725175405.ABE763A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/8ea1835091a42328a9ab152aa2ab3d759f90a06c/ghc >--------------------------------------------------------------- commit 8ea1835091a42328a9ab152aa2ab3d759f90a06c Author: Ben Gamari Date: Fri Jul 21 00:11:14 2017 -0400 Debugging ghc-pkg >--------------------------------------------------------------- 8ea1835091a42328a9ab152aa2ab3d759f90a06c libraries/ghc-boot/GHC/PackageDb.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/ghc-boot/GHC/PackageDb.hs b/libraries/ghc-boot/GHC/PackageDb.hs index bf83d25..f1ccf16 100644 --- a/libraries/ghc-boot/GHC/PackageDb.hs +++ b/libraries/ghc-boot/GHC/PackageDb.hs @@ -352,7 +352,7 @@ getHeader :: Get (Word32, Word32) getHeader = do magic <- getByteString (BS.length headerMagic) when (magic /= headerMagic) $ - fail "not a ghc-pkg db file, wrong file magic number" + fail $ "not a ghc-pkg db file, wrong file magic number (saw "++show magic++", expected "++show headerMagic++")" majorVersion <- get :: Get Word32 -- The major version is for incompatible changes From git at git.haskell.org Tue Jul 25 17:54:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 17:54:14 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: llvmGen: Fix another (70ace6a) Message-ID: <20170725175414.301F33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/70ace6abcfddd004e7df90daddea2652f535946f/ghc >--------------------------------------------------------------- commit 70ace6abcfddd004e7df90daddea2652f535946f Author: Ben Gamari Date: Fri Jul 21 00:18:20 2017 -0400 llvmGen: Fix another >--------------------------------------------------------------- 70ace6abcfddd004e7df90daddea2652f535946f compiler/llvmGen/LlvmCodeGen.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/compiler/llvmGen/LlvmCodeGen.hs b/compiler/llvmGen/LlvmCodeGen.hs index 121e3b9..dff5c44 100644 --- a/compiler/llvmGen/LlvmCodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen.hs @@ -23,7 +23,6 @@ import Hoopl.Block import Hoopl.Collections import PprCmm -import BufWrite import DynFlags import ErrUtils import FastString From git at git.haskell.org Tue Jul 25 17:54:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 17:54:16 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: Never tick primitive string literals (806c398) Message-ID: <20170725175416.E565B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/806c39855db0e5bd6d929b82d2a70c43b2b9a39f/ghc >--------------------------------------------------------------- commit 806c39855db0e5bd6d929b82d2a70c43b2b9a39f Author: Ben Gamari Date: Fri Jul 21 01:23:26 2017 -0400 Never tick primitive string literals Summary: 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: scpmw, simonmar, dfeuer, simonpj, austin Subscribers: dfeuer, simonmar, thomie Differential Revision: https://phabricator.haskell.org/D3063 >--------------------------------------------------------------- 806c39855db0e5bd6d929b82d2a70c43b2b9a39f compiler/coreSyn/CoreSyn.hs | 2 ++ compiler/coreSyn/CoreUtils.hs | 5 +++++ compiler/simplCore/FloatOut.hs | 32 ++++++++++++-------------------- compiler/simplCore/Simplify.hs | 15 +++------------ 4 files changed, 22 insertions(+), 32 deletions(-) diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs index 99478d2..41202c3 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 +primitive 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 540a36e..3b80fb6 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -300,6 +300,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..06062bd 100644 --- a/compiler/simplCore/FloatOut.hs +++ b/compiler/simplCore/FloatOut.hs @@ -21,7 +21,6 @@ import DynFlags import ErrUtils ( dumpIfSet_dyn ) import Id ( Id, idArity, idType, isBottomingId, isJoinId, isJoinId_maybe ) -import BasicTypes ( TopLevelFlag(..), isTopLevel ) import SetLevels import UniqSupply ( UniqSupply ) import Bag @@ -735,26 +734,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 91ed644..7b11595 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -611,19 +611,10 @@ 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) - floats' = seLetFloats env `addFlts` - mapFloats (seLetFloats env') tickIt + ; 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') } go _ env other From git at git.haskell.org Tue Jul 25 17:54:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 17:54:08 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: llvmGen: Clean up warning (8ed5a85) Message-ID: <20170725175408.744653A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/8ed5a85e0a62158b287164b6b83adb58cfe789fd/ghc >--------------------------------------------------------------- commit 8ed5a85e0a62158b287164b6b83adb58cfe789fd Author: Ben Gamari Date: Fri Jul 21 00:16:34 2017 -0400 llvmGen: Clean up warning >--------------------------------------------------------------- 8ed5a85e0a62158b287164b6b83adb58cfe789fd compiler/llvmGen/LlvmCodeGen/Base.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index 99202b7..6e42f52 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -49,7 +49,6 @@ import Outputable as Outp import Platform import UniqFM import Unique -import BufWrite ( BufHandle ) import System.IO (Handle) import UniqSet import UniqSupply From git at git.haskell.org Tue Jul 25 17:54:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 17:54:11 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: nativeGen: Clean up warning (f2a305b) Message-ID: <20170725175411.747363A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/f2a305b5944eac0cfd9136bf7b0de78f983070b6/ghc >--------------------------------------------------------------- commit f2a305b5944eac0cfd9136bf7b0de78f983070b6 Author: Ben Gamari Date: Fri Jul 21 00:17:27 2017 -0400 nativeGen: Clean up warning >--------------------------------------------------------------- f2a305b5944eac0cfd9136bf7b0de78f983070b6 compiler/nativeGen/AsmCodeGen.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/compiler/nativeGen/AsmCodeGen.hs b/compiler/nativeGen/AsmCodeGen.hs index e791b86..11bd8a1 100644 --- a/compiler/nativeGen/AsmCodeGen.hs +++ b/compiler/nativeGen/AsmCodeGen.hs @@ -98,7 +98,6 @@ import Data.Maybe import Data.Ord ( comparing ) import Control.Exception import Control.Monad -import System.IO import System.IO (Handle) {- From git at git.haskell.org Tue Jul 25 17:54:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 17:54:19 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: ghc-prim: Don't allocate a thunk for each unpacked UTF-8 character (60c3063) Message-ID: <20170725175419.A09F63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/60c306369c8344f378707894039c3901788dafb4/ghc >--------------------------------------------------------------- commit 60c306369c8344f378707894039c3901788dafb4 Author: Ben Gamari Date: Fri Jul 21 12:00:48 2017 -0400 ghc-prim: Don't allocate a thunk for each unpacked UTF-8 character While debugging #14005 I noticed that unpackCStringUtf8# was allocating a thunk for each Unicode character that it unpacked. This seems hardly worthwhile given that the thunk's closure will be at least three words, whereas the Char itself will be only two and requires only a bit of bit twiddling to construct. >--------------------------------------------------------------- 60c306369c8344f378707894039c3901788dafb4 libraries/ghc-prim/GHC/CString.hs | 24 ++++++++++++------------ 1 file changed, 12 insertions(+), 12 deletions(-) diff --git a/libraries/ghc-prim/GHC/CString.hs b/libraries/ghc-prim/GHC/CString.hs index cdda2db..e739af7 100644 --- a/libraries/ghc-prim/GHC/CString.hs +++ b/libraries/ghc-prim/GHC/CString.hs @@ -129,20 +129,20 @@ unpackCStringUtf8# addr | isTrue# (ch `eqChar#` '\0'# ) = [] | isTrue# (ch `leChar#` '\x7F'#) = C# ch : unpack (nh +# 1#) | isTrue# (ch `leChar#` '\xDF'#) = - C# (chr# (((ord# ch -# 0xC0#) `uncheckedIShiftL#` 6#) +# - (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#))) : - unpack (nh +# 2#) + let !c = C# (chr# (((ord# ch -# 0xC0#) `uncheckedIShiftL#` 6#) +# + (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#))) + in c : unpack (nh +# 2#) | isTrue# (ch `leChar#` '\xEF'#) = - C# (chr# (((ord# ch -# 0xE0#) `uncheckedIShiftL#` 12#) +# - ((ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#` 6#) +# - (ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#))) : - unpack (nh +# 3#) + let !c = C# (chr# (((ord# ch -# 0xE0#) `uncheckedIShiftL#` 12#) +# + ((ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#` 6#) +# + (ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#))) + in c : unpack (nh +# 3#) | True = - C# (chr# (((ord# ch -# 0xF0#) `uncheckedIShiftL#` 18#) +# - ((ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#` 12#) +# - ((ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#) `uncheckedIShiftL#` 6#) +# - (ord# (indexCharOffAddr# addr (nh +# 3#)) -# 0x80#))) : - unpack (nh +# 4#) + let !c = C# (chr# (((ord# ch -# 0xF0#) `uncheckedIShiftL#` 18#) +# + ((ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#` 12#) +# + ((ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#) `uncheckedIShiftL#` 6#) +# + (ord# (indexCharOffAddr# addr (nh +# 3#)) -# 0x80#))) + in c : unpack (nh +# 4#) where !ch = indexCharOffAddr# addr nh From git at git.haskell.org Tue Jul 25 17:54:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 17:54:25 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: Start of annotating core (8b50cd4) Message-ID: <20170725175425.AF9083A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/8b50cd4721f87a3d37254494d56d0388fd4c9b5f/ghc >--------------------------------------------------------------- commit 8b50cd4721f87a3d37254494d56d0388fd4c9b5f Author: Matthew Pickering Date: Tue Jul 25 16:59:55 2017 +0000 Start of annotating core >--------------------------------------------------------------- 8b50cd4721f87a3d37254494d56d0388fd4c9b5f compiler/coreSyn/PprCore.hs | 9 ++++++++- compiler/ghc.cabal.in | 1 + compiler/ghc.mk | 1 + compiler/utils/Outputable.hs | 20 +++++++++++++++----- compiler/utils/OutputableAnnotation.hs | 9 +++++++++ compiler/utils/OutputableAnnotation.hs-boot | 3 +++ compiler/utils/Pretty.hs | 1 + 7 files changed, 38 insertions(+), 6 deletions(-) diff --git a/compiler/coreSyn/PprCore.hs b/compiler/coreSyn/PprCore.hs index 28d3552..da78d1e 100644 --- a/compiler/coreSyn/PprCore.hs +++ b/compiler/coreSyn/PprCore.hs @@ -12,7 +12,7 @@ module PprCore ( pprCoreExpr, pprParendExpr, pprCoreBinding, pprCoreBindings, pprCoreAlt, pprCoreBindingWithSize, pprCoreBindingsWithSize, - pprRules, pprOptCo + pprRules, pprOptCo, pprCoreBindingsWithAnn ) where import CoreSyn @@ -32,6 +32,7 @@ import BasicTypes import Maybes import Util import Outputable +import OutputableAnnotation import FastString import SrcLoc ( pprUserRealSpan ) @@ -65,6 +66,9 @@ instance OutputableBndr b => Outputable (Bind b) where instance OutputableBndr b => Outputable (Expr b) where ppr expr = pprCoreExpr expr +pprCoreBindingsWithAnn :: [CoreBind] -> SDoc +pprCoreBindingsWithAnn = pprTopBinds realAnn + {- ************************************************************************ * * @@ -80,6 +84,9 @@ type Annotation b = Expr b -> SDoc sizeAnn :: CoreExpr -> SDoc sizeAnn e = text "-- RHS size:" <+> ppr (exprStats e) +realAnn :: CoreExpr -> SDoc +realAnn e = addAnn (PCoreExpr e) (ppr e) + -- | No annotation noAnn :: Expr b -> SDoc noAnn _ = empty diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index 4f2db5e..49c8cb9 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -506,6 +506,7 @@ Library MonadUtils OrdList Outputable + OutputableAnnotation Pair Panic PprColour diff --git a/compiler/ghc.mk b/compiler/ghc.mk index bfd75ab..95d6fab 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -526,6 +526,7 @@ compiler_stage2_dll0_MODULES = \ OptCoercion \ OrdList \ Outputable \ + OutputableAnnotation \ PackageConfig \ Packages \ Pair \ diff --git a/compiler/utils/Outputable.hs b/compiler/utils/Outputable.hs index 08e5719..ba4bc7e 100644 --- a/compiler/utils/Outputable.hs +++ b/compiler/utils/Outputable.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, ImplicitParams #-} +{-# LANGUAGE CPP, ImplicitParams, GADTs #-} {- (c) The University of Glasgow 2006-2012 (c) The GRASP Project, Glasgow University, 1992-1998 @@ -40,6 +40,8 @@ module Outputable ( coloured, keyword, + addAnn, + -- * Converting 'SDoc' into strings and outputing it printSDoc, printSDocLn, printForUser, printForUserPartWay, printForC, bufLeftRenderSDoc, @@ -82,6 +84,7 @@ module Outputable ( pprTrace, pprTraceDebug, pprTraceIt, warnPprTrace, pprSTrace, trace, pgmError, panic, sorry, assertPanic, pprDebugAndThen, callStackDoc + ) where import {-# SOURCE #-} DynFlags( DynFlags, hasPprDebug, hasNoDebugOutput, @@ -91,13 +94,15 @@ import {-# SOURCE #-} DynFlags( DynFlags, hasPprDebug, hasNoDebugOutput, import {-# SOURCE #-} Module( UnitId, Module, ModuleName, moduleName ) import {-# SOURCE #-} OccName( OccName ) +import {-# SOURCE #-} OutputableAnnotation + import BufWrite (BufHandle) import FastString import qualified Pretty import Util import Platform import qualified PprColour as Col -import Pretty ( Doc, Mode(..) ) +import Pretty ( Doc, Mode(..), annotate ) import Panic import GHC.Serialized import GHC.LanguageExtensions (Extension) @@ -122,6 +127,7 @@ import Data.List (intersperse) import GHC.Fingerprint import GHC.Show ( showMultiLineString ) +import Data.Void {- ************************************************************************ @@ -306,6 +312,7 @@ code (either C or assembly), or generating interface files. ************************************************************************ -} + -- | Represents a pretty-printable document. -- -- To display an 'SDoc', use 'printSDoc', 'printSDocLn', 'bufLeftRenderSDoc', @@ -313,7 +320,10 @@ code (either C or assembly), or generating interface files. -- abstraction layer. -- Note that for now, it is Doc (). This should be changed to hold -- annotation. -newtype SDoc = SDoc { runSDoc :: SDocContext -> Doc () } +newtype SDoc = SDoc { runSDoc :: SDocContext -> Doc PExpr } + +addAnn :: PExpr -> SDoc -> SDoc +addAnn pe (SDoc s) = (SDoc (\ctx -> annotate pe (s ctx))) data SDocContext = SDC { sdocStyle :: !PprStyle @@ -338,7 +348,7 @@ withPprStyle sty d = SDoc $ \ctxt -> runSDoc d ctxt{sdocStyle=sty} -- | This is not a recommended way to render 'SDoc', since it breaks the -- abstraction layer of 'SDoc'. Prefer to use 'printSDoc', 'printSDocLn', -- 'bufLeftRenderSDoc', or 'renderWithStyle' instead. -withPprStyleDoc :: DynFlags -> PprStyle -> SDoc -> Doc () +withPprStyleDoc :: DynFlags -> PprStyle -> SDoc -> Doc PExpr withPprStyleDoc dflags sty d = runSDoc d (initSDocContext dflags sty) sdocWithPprDebug :: (Bool -> SDoc) -> SDoc @@ -541,7 +551,7 @@ isEmpty :: DynFlags -> SDoc -> Bool isEmpty dflags sdoc = Pretty.isEmpty $ runSDoc sdoc dummySDocContext where dummySDocContext = initSDocContext dflags PprDebug -docToSDoc :: Doc () -> SDoc +docToSDoc :: Doc PExpr -> SDoc docToSDoc d = SDoc (\_ -> d) empty :: SDoc diff --git a/compiler/utils/OutputableAnnotation.hs b/compiler/utils/OutputableAnnotation.hs new file mode 100644 index 0000000..f506a0b --- /dev/null +++ b/compiler/utils/OutputableAnnotation.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE GADTs #-} +module OutputableAnnotation (PExpr(..)) where + +import CoreSyn + +data PExpr where + PCoreExpr :: CoreExpr -> PExpr + + diff --git a/compiler/utils/OutputableAnnotation.hs-boot b/compiler/utils/OutputableAnnotation.hs-boot new file mode 100644 index 0000000..d71f632 --- /dev/null +++ b/compiler/utils/OutputableAnnotation.hs-boot @@ -0,0 +1,3 @@ +module OutputableAnnotation where + +data PExpr diff --git a/compiler/utils/Pretty.hs b/compiler/utils/Pretty.hs index a7969e6..f35d692 100644 --- a/compiler/utils/Pretty.hs +++ b/compiler/utils/Pretty.hs @@ -108,6 +108,7 @@ module Pretty ( -- ** GHC-specific rendering printDoc, printDoc_, -- bufLeftRender -- performance hack + annotate ) where From git at git.haskell.org Tue Jul 25 17:54:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 17:54:22 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: Hack: Produce latin1 asm output (5256c89) Message-ID: <20170725175422.5AE853A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/5256c89d3172d353d4ebc595b8c38c7ae5a796c9/ghc >--------------------------------------------------------------- commit 5256c89d3172d353d4ebc595b8c38c7ae5a796c9 Author: Ben Gamari Date: Fri Jul 21 14:28:57 2017 -0400 Hack: Produce latin1 asm output >--------------------------------------------------------------- 5256c89d3172d353d4ebc595b8c38c7ae5a796c9 compiler/nativeGen/AsmCodeGen.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/nativeGen/AsmCodeGen.hs b/compiler/nativeGen/AsmCodeGen.hs index 11bd8a1..ec6f113 100644 --- a/compiler/nativeGen/AsmCodeGen.hs +++ b/compiler/nativeGen/AsmCodeGen.hs @@ -98,7 +98,7 @@ import Data.Maybe import Data.Ord ( comparing ) import Control.Exception import Control.Monad -import System.IO (Handle) +import System.IO {- The native-code generator has machine-independent and @@ -330,6 +330,7 @@ nativeCodeGen' :: (Outputable statics, Outputable instr, Instruction instr) -> IO UniqSupply nativeCodeGen' dflags this_mod modLoc ncgImpl h us cmms = do + hSetEncoding h latin1 let ngs0 = NGS [] [] [] [] [] [] emptyUFM mapEmpty (ngs, us') <- cmmNativeGenStream dflags this_mod modLoc ncgImpl h us cmms ngs0 From git at git.haskell.org Tue Jul 25 20:17:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 20:17:35 +0000 (UTC) Subject: [commit: ghc] master: Fix #10684 by processing deriving clauses with finer grain (6bb32ba) Message-ID: <20170725201735.E74E13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6bb32ba78580271921e3d5c3c98afac2c1b68de4/ghc >--------------------------------------------------------------- commit 6bb32ba78580271921e3d5c3c98afac2c1b68de4 Author: Ryan Scott Date: Tue Jul 25 16:14:27 2017 -0400 Fix #10684 by processing deriving clauses with finer grain Summary: Previously, one could experience error cascades with deriving clauses when one class in a set of many failed to derive, causing the other derived classes to be skipped entirely and resulting in other errors down the line. The solution is to process each class in a data type's set of deriving clauses individually, and engineer it so that failure to derive an individual class within that set doesn't cancel out the others. Test Plan: make test TEST="T10684 T12801" Reviewers: austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #10684, #12801 Differential Revision: https://phabricator.haskell.org/D3771 >--------------------------------------------------------------- 6bb32ba78580271921e3d5c3c98afac2c1b68de4 compiler/typecheck/TcDeriv.hs | 109 +++++++++++++++++---- testsuite/tests/deriving/should_fail/T10684.hs | 4 + testsuite/tests/deriving/should_fail/T10684.stderr | 5 + testsuite/tests/deriving/should_fail/T12801.hs | 8 ++ testsuite/tests/deriving/should_fail/T12801.stderr | 5 + testsuite/tests/deriving/should_fail/all.T | 2 + 6 files changed, 113 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 6bb32ba78580271921e3d5c3c98afac2c1b68de4 From git at git.haskell.org Tue Jul 25 20:27:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 20:27:12 +0000 (UTC) Subject: [commit: ghc] wip/T13904: update to current master (8ddb47c) Message-ID: <20170725202712.24D073A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T13904 Link : http://ghc.haskell.org/trac/ghc/changeset/8ddb47cfcf5776e9a3c55fd37947c8a95e00fa12/ghc >--------------------------------------------------------------- commit 8ddb47cfcf5776e9a3c55fd37947c8a95e00fa12 Merge: baea1d6 6bb32ba Author: Kavon Farvardin Date: Tue Jul 25 15:25:37 2017 -0500 update to current master >--------------------------------------------------------------- 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 8ddb47cfcf5776e9a3c55fd37947c8a95e00fa12 From git at git.haskell.org Tue Jul 25 20:27:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Jul 2017 20:27:15 +0000 (UTC) Subject: [commit: ghc] wip/T13904's head updated: update to current master (8ddb47c) Message-ID: <20170725202715.10BB13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T13904' now includes: 0592318 Fix paper link in MVar docs [ci skip] 544ac0d rename tcInstBinder(s)X to tcInstBinder(s) 84d6831a users-guide: Wibbles in shared libraries discussion 287a405 Allow per-argument documentation on pattern synonym signatures 1a9c3c4 Implement recompilation checking for -fignore-asserts f9c6d53 Tag the FUN before making a PAP (#13767) c3a7862 Fix #13311 by using tcSplitNestedSigmaTys in the right place d55bea1 Fix -fno-code for modules that use -XQuasiQuotes 0c1f905 CmmParse: Emit source notes for assignments 5aee331 Bump array submodule to v0.5.2.0 8f8d756 rts: Fix uninitialised variable uses af403b2 ApplicativeDo: document behaviour with strict patterns (#13875) ef63ff2 configure: Remove --with-curses-includes flag a6f3d1b rts: Fix isByteArrayPinned#'s treatment of large arrays 960918b Add -fuse-ld flag to CFLAGS during configure 0836bfb testsuite: Add testcase for #13615 fd7a7a6 Eagerly blackhole AP_STACKs 9492703 rts/sm/Storage.c: tweak __clear_cache proto for clang 7040660 Revert "rts/sm/Storage.c: tweak __clear_cache proto for clang" 3eeb55e rts/sm/Storage.c: tweak __clear_cache proto for clang 555e5cc rts: Address AP_STACK comment suggestion from Simon 4997177 mkDocs: Don't install *.ps f3979b7 lowercase clang 99adcc8 Typos in comments [ci skip] bd4fdc6 Implement split-sections support for windows. c2303df aclocal.m4: allow arbitrary string in toolchain triplets e1146ed Fix typos in Bag.hs [ci skip] 81377e9 Big-obj support for the Windows runtime linker c506f83 Pretty-printer no longer butchers function arrow fixity 4f69013 testsuite: Decrease T13701 allocations 31ceaba user-guide: Various fixes to FFI section 905dc8b Make ':info Coercible' display an arbitrary string (fixes #12390) 7c9e356 Fix Work Balance computation in RTS stats b0c9f34 Improve Wmissing-home-modules warning under Cabal 6cff2ca Add testcase for T13818 15fcd9a Suppress unused warnings for selectors for some derived classes cb8db9b Sort list of failed tests for easier comparison between runs b8f33bc Always allow -staticlib fe6618b ByteCodeGen: use depth instead of offsets in BCEnv ccb849f users-guide/rel-notes: Describe #13875 fix 81de42c Add Template Haskell support for overloaded labels abda03b Optimize TimerManager ea75124 Fix logic error in GhcMake.enableCodeGenForTH ba46e63 Fix #13948 by being pickier about when to suggest DataKinds 85ac65c Fix #13947 by checking for unbounded names more ef7fd0a Parenthesize infix type names in data declarations in TH printer ec351b8 Add Template Haskell support for overloaded labels a249e93 Remove unnecessarily returned res_ty from rejigConRes d3bdd6c testsuite: Fix T13701 allocations yet again fcd2db1 configure: Ensure that we don't set LD to unusable linker be04c16 StgLint: Don't loop on tycons with runtime rep arguments 20880b5 testsuite: Show stderr output on command failure a0d9169 Fix minor typo 3a163aa Remove redundant import; fix note 4befb41 Mention which -Werror promoted a warning to an error 9b9f978 Use correct section types syntax for architecture 1ee49cb Fix missing escape in macro 60ec8f7 distrib/configure: Fail if we can't detect machine's word size 7ae4a28 [iserv] Fixing the word size for RemotePtr and toWordArray 5743581 testsuite: Update haddock allocations 4700baa testsuite: Again update allocations of T13701 1909985 Fix some excessive spacing in error messages f656fba [skip ci] Temporarily disable split-sections on Windows. 12ae1fa Fix a missing getNewNursery(), and related cleanup 935acb6 Typos in comments and explanation for unusused imports b8fec69 Make module membership on ModuleGraph faster 6ab3c5f Typeable: Always use UTF-8 string unpacking primitive d7b1751 configure: Cleanup ARM COPY bug test artifacts a051b55 testsuite: Ensure that hs_try_putmvar003 terminates c9e4c86 Allow visible type application for [] 1ed41a7 Fix links to SPJ’s papers (fixes #12578) 0b89b2d Add Haddocks for Eq (STRef a) and Eq (IORef a) c940e3b dmdAnal: Ensure that ExnStr flag isn't dropped inappropriately 6e3c901 Fix #13983 by creating a TyConFlavour type, and using it 927e781 typo: -XUndeci[d]ableInstances b066d93 base: Improve docs to clarify when finalizers may not be run cc839c5 Typeable: Ensure that promoted data family instance tycons get bindings a273c73 Spelling fixes eeb141d Demand: Improve comments 8e51bfc Introduce -fcatch-bottoms c9c762d testsuite: Pipe stdin directly to process a85a595 arcconfig: Set project ruleset to use master merge-base by default 194384f Fix busy-wait in SysTools.builderMainLoop fdb6a5b Make IfaceAxiom typechecking lazier. 5469ac8 Interpreter.c: use macros to access/modify Sp bade356 rts: Claim AP_STACK before adjusting Sp 1480080 distrib/configure: Canonicalize triples b2d3ec3 testsuite: Add test for #13916 ccac387 Revert "testsuite: Add test for #13916" 36e8bcb HsPat: Assume that no spliced patterns are irrefutable fefcbfa build system: Ensure there are no duplicate files in bindist list acbbb50 Fix ungrammatical error message cbbf083 fix dllwrap issue. c1d9690 Avoid linear lookup in unload_wkr in the Linker ee1047e Update autoconf scripts 98ab12a distrib/configure: Carry FFI include/lib paths from source distribution fb08252 users-guide: Improve legibility of OverlappingInstances documentation 0ae0f46 Preserve HaskellHaveRTSLinker in bindist 646ec0e Bump a bunch of submodules b8afdaf Update release notes for 8.2.1 fb17cc5 Bump integer-gmp version ecc9e9a ghc-prim: Bump version d4e9721 testsuite: Fix cabal01 for real this time 44b090b users-guide: Standardize and repair all flag references c945195 users-guide: Fix various wibbles 2dff2c7 Fix more documentation wibbles 145f1c7 Remove 8.0.2 release notes file 88f20bd Add a caveat to the GHC.Generics examples about :+: nesting a602b65 users-guides: Fix errant whitespace 0c04d78 users-guide: Cross-reference more flags 58b62d6 users-guide: Eliminate some redundant index entries 3e5d0f1 users-guide: Make it easier to reference haddocks 897366a users-guide: Fix URL of deferred type errors paper 85a295d ghc-prim: Don't allocate a thunk for each unpacked UTF-8 character 8a8cee7 DynFlags: Drop rtsBuildTag field d8051c6 Use libpthread instead of libthr on FreeBSD 8ec7770 testsuite: Add testcase for #13168 2183ac1 Fix import error with -XPackageImports when the module has a duplicate name 58545fd base: Introduce GHC.ByteOrder 104c72b Expose FrontendPluginAction 7d1909a Remove unused language pragma 36b270a Revert "Remove unused language pragma" 6bb32ba Fix #10684 by processing deriving clauses with finer grain 8ddb47c update to current master From git at git.haskell.org Wed Jul 26 11:34:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 11:34:12 +0000 (UTC) Subject: [commit: ghc] master: Fix binder visiblity for default methods (75bf11c) Message-ID: <20170726113412.40C793A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/75bf11c037d9e82f95ac9779bfd2b1432835bd76/ghc >--------------------------------------------------------------- commit 75bf11c037d9e82f95ac9779bfd2b1432835bd76 Author: Simon Peyton Jones Date: Wed Jul 26 08:51:47 2017 +0100 Fix binder visiblity for default methods Trac #13998 showed that default methods were getting bogus tyvar binder visiblity info; and that it matters in the code genreated by the default-method fill-in mechanism * The actual fix: in TcTyDecls.mkDefaultMethodType, make TyVarBinders with the right visibility info by getting TyConBinders from the class TyCon. (Previously we made up visiblity info, but that caused #13998.) * Define TyCon.tyConTyVarBinders :: [TyConBinder] -> [TyVarBinder] which can build correct forall binders for a) default methods (Trac #13998) b) data constructors This was originally BuildTyCl.mkDataConUnivTyVarBinders * Move mkTyVarBinder, mkTyVarBinders from Type to Var >--------------------------------------------------------------- 75bf11c037d9e82f95ac9779bfd2b1432835bd76 compiler/basicTypes/Var.hs | 11 +++- compiler/iface/BuildTyCl.hs | 70 +--------------------- compiler/iface/TcIface.hs | 2 +- compiler/typecheck/TcPatSyn.hs | 3 +- compiler/typecheck/TcTyClsDecls.hs | 2 +- compiler/typecheck/TcTyDecls.hs | 14 ++++- compiler/typecheck/TcType.hs | 2 +- compiler/types/Class.hs | 4 ++ compiler/types/TyCoRep.hs | 54 ++++++++++------- compiler/types/TyCon.hs | 72 ++++++++++++++++++++++- compiler/types/Type.hs | 8 --- testsuite/tests/deriving/should_compile/T13998.hs | 43 ++++++++++++++ testsuite/tests/deriving/should_compile/all.T | 1 + 13 files changed, 177 insertions(+), 109 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 75bf11c037d9e82f95ac9779bfd2b1432835bd76 From git at git.haskell.org Wed Jul 26 11:34:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 11:34:15 +0000 (UTC) Subject: [commit: ghc] master: Comments and tc-tracing only (6386fc3) Message-ID: <20170726113415.016613A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6386fc320b25b0d7d6dbf9356cb984f28bb23d3e/ghc >--------------------------------------------------------------- commit 6386fc320b25b0d7d6dbf9356cb984f28bb23d3e Author: Simon Peyton Jones Date: Wed Jul 26 08:57:16 2017 +0100 Comments and tc-tracing only >--------------------------------------------------------------- 6386fc320b25b0d7d6dbf9356cb984f28bb23d3e compiler/typecheck/TcInteract.hs | 11 +++++++---- compiler/typecheck/TcSMonad.hs | 2 +- compiler/typecheck/TcType.hs | 5 ++++- 3 files changed, 12 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 83dc10c..69e84a4 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -527,7 +527,8 @@ solveOneFromTheOther ev_i ev_w | CtWanted { ctev_loc = loc_w } <- ev_w , prohibitedSuperClassSolve (ctEvLoc ev_i) loc_w - = return (IRDelete, False) + = do { traceTcS "prohibitedClassSolve1" (ppr ev_i $$ ppr ev_w) + ; return (IRDelete, False) } | CtWanted { ctev_dest = dest } <- ev_w -- Inert is Given or Wanted @@ -536,9 +537,10 @@ solveOneFromTheOther ev_i ev_w | CtWanted { ctev_loc = loc_i } <- ev_i -- Work item is Given , prohibitedSuperClassSolve (ctEvLoc ev_w) loc_i - = return (IRKeep, False) -- Just discard the un-usable Given - -- This never actually happens because - -- Givens get processed first + = do { traceTcS "prohibitedClassSolve2" (ppr ev_i $$ ppr ev_w) + ; return (IRKeep, False) } -- Just discard the un-usable Given + -- This never actually happens because + -- Givens get processed first | CtWanted { ctev_dest = dest } <- ev_i = do { setWantedEvTerm dest (ctEvTerm ev_w) @@ -877,6 +879,7 @@ interactDict inerts workItem@(CDictCan { cc_ev = ev_w, cc_class = cls, cc_tyargs -- we solve it from the solution in the inerts we just retrieved. Nothing -> do { (inert_effect, stop_now) <- solveOneFromTheOther ctev_i ev_w + ; traceTcS "lookupInertDict" (ppr inert_effect <+> ppr stop_now) ; case inert_effect of IRKeep -> return () IRDelete -> updInertDicts $ \ ds -> delDict ds cls tys diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index b5f6554..92b753f 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -2067,7 +2067,7 @@ solvable from the other. So, we do lookup in the inert set using loose types, which omit the kind-check. We must be careful when using the result of a lookup because it may -not match the requsted info exactly! +not match the requested info exactly! -} diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index 00bcea2..7b8ff13 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -2559,8 +2559,11 @@ sizeType = go go (TyVarTy {}) = 1 go (TyConApp tc tys) | isTypeFamilyTyCon tc = infinity -- Type-family applications can - -- expand to any arbitrary size + -- expand to any arbitrary size | otherwise = sizeTypes (filterOutInvisibleTypes tc tys) + 1 + -- Why filter out invisible args? I suppose any + -- size ordering is sound, but why is this better? + -- I came across this when investigating #14010. go (LitTy {}) = 1 go (FunTy arg res) = go arg + go res + 1 go (AppTy fun arg) = go fun + go arg From git at git.haskell.org Wed Jul 26 11:34:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 11:34:17 +0000 (UTC) Subject: [commit: ghc] master: Comments only (f959624) Message-ID: <20170726113417.B70803A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f959624f2a0f274a16a981ca7c866020082531f6/ghc >--------------------------------------------------------------- commit f959624f2a0f274a16a981ca7c866020082531f6 Author: Simon Peyton Jones Date: Wed Jul 26 08:57:41 2017 +0100 Comments only >--------------------------------------------------------------- f959624f2a0f274a16a981ca7c866020082531f6 compiler/simplCore/Simplify.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index 91ed644..dd0d45b 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -566,7 +566,6 @@ That's what the 'go' loop in prepareRhs does prepareRhs :: TopLevelFlag -> SimplEnv -> OutId -> OutExpr -> SimplM (SimplEnv, OutExpr) -- See Note [prepareRhs] -- Adds new floats to the env iff that allows us to return a good RHS --- See Note [prepareRhs] prepareRhs top_lvl env id (Cast rhs co) -- Note [Float coercions] | Pair ty1 _ty2 <- coercionKind co -- Do *not* do this if rhs has an unlifted type , not (isUnliftedType ty1) -- see Note [Float coercions (unlifted)] From git at git.haskell.org Wed Jul 26 11:34:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 11:34:08 +0000 (UTC) Subject: [commit: ghc] master: Add an Outputable instance for ListMap (746ab0b) Message-ID: <20170726113408.AE8593A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/746ab0b4a2f97d9f2a97fc28431e5bdfbc10b8cf/ghc >--------------------------------------------------------------- commit 746ab0b4a2f97d9f2a97fc28431e5bdfbc10b8cf Author: Simon Peyton Jones Date: Wed Jul 26 08:31:47 2017 +0100 Add an Outputable instance for ListMap >--------------------------------------------------------------- 746ab0b4a2f97d9f2a97fc28431e5bdfbc10b8cf compiler/coreSyn/TrieMap.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/compiler/coreSyn/TrieMap.hs b/compiler/coreSyn/TrieMap.hs index a6b9db4..fcff256 100644 --- a/compiler/coreSyn/TrieMap.hs +++ b/compiler/coreSyn/TrieMap.hs @@ -278,6 +278,9 @@ instance TrieMap m => TrieMap (ListMap m) where foldTM = fdList mapTM = mapList +instance (TrieMap m, Outputable a) => Outputable (ListMap m a) where + ppr m = text "List elts" <+> ppr (foldTM (:) m []) + mapList :: TrieMap m => (a->b) -> ListMap m a -> ListMap m b mapList f (LM { lm_nil = mnil, lm_cons = mcons }) = LM { lm_nil = fmap f mnil, lm_cons = mapTM (mapTM f) mcons } From git at git.haskell.org Wed Jul 26 11:34:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 11:34:21 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #14033 (d31181b) Message-ID: <20170726113421.1EAA63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d31181b90cff7c791465687377cd2093627df429/ghc >--------------------------------------------------------------- commit d31181b90cff7c791465687377cd2093627df429 Author: Simon Peyton Jones Date: Wed Jul 26 11:30:55 2017 +0100 Test Trac #14033 >--------------------------------------------------------------- d31181b90cff7c791465687377cd2093627df429 testsuite/tests/indexed-types/should_fail/T14033.hs | 10 ++++++++++ testsuite/tests/indexed-types/should_fail/T14033.stderr | 6 ++++++ testsuite/tests/indexed-types/should_fail/all.T | 1 + 3 files changed, 17 insertions(+) diff --git a/testsuite/tests/indexed-types/should_fail/T14033.hs b/testsuite/tests/indexed-types/should_fail/T14033.hs new file mode 100644 index 0000000..2c8ab68 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T14033.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TypeFamilies #-} + +module T14033 where + +newtype Zero = Zero +newtype Succ a = Succ a + +type family Add n m :: * where + Add Zero m = m + Add (Succ n) m = Succ (Add n m) diff --git a/testsuite/tests/indexed-types/should_fail/T14033.stderr b/testsuite/tests/indexed-types/should_fail/T14033.stderr new file mode 100644 index 0000000..fbc6b54 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T14033.stderr @@ -0,0 +1,6 @@ + +T14033.hs:5:16: error: + • The constructor of a newtype must have exactly one field + but ‘Zero’ has none + • In the definition of data constructor ‘Zero’ + In the newtype declaration for ‘Zero’ diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index 50257e6..8885933 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -135,3 +135,4 @@ test('T7102a', normal, ghci_script, ['T7102a.script']) test('T13271', normal, compile_fail, ['']) test('T13674', normal, compile_fail, ['']) test('T13784', normal, compile_fail, ['']) +test('T14033', normal, compile_fail, ['']) From git at git.haskell.org Wed Jul 26 11:35:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 11:35:25 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: Use my branch of haddock (ef6702c) Message-ID: <20170726113525.3C7E43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/ef6702c61d991c095622f4c8fefc5130f6ae96e8/ghc >--------------------------------------------------------------- commit ef6702c61d991c095622f4c8fefc5130f6ae96e8 Author: Matthew Pickering Date: Wed Jul 26 11:34:58 2017 +0000 Use my branch of haddock >--------------------------------------------------------------- ef6702c61d991c095622f4c8fefc5130f6ae96e8 .gitmodules | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.gitmodules b/.gitmodules index 05ca581..b6513e4 100644 --- a/.gitmodules +++ b/.gitmodules @@ -104,9 +104,9 @@ ignore = none [submodule "utils/haddock"] path = utils/haddock - url = ../haddock.git + url = git at github.com:mpickering/haddock.git ignore = none - branch = ghc-head + branch = wip/T14005 [submodule "nofib"] path = nofib url = ../nofib.git From git at git.haskell.org Wed Jul 26 11:38:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 11:38:18 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: Add the correct commit (0d05c7b) Message-ID: <20170726113818.DFD223A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/0d05c7bff52a2975a1a41b5de1ead155b5401aad/ghc >--------------------------------------------------------------- commit 0d05c7bff52a2975a1a41b5de1ead155b5401aad Author: Matthew Pickering Date: Wed Jul 26 11:38:07 2017 +0000 Add the correct commit >--------------------------------------------------------------- 0d05c7bff52a2975a1a41b5de1ead155b5401aad utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 7cecbd9..5716d69 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 7cecbd969298d5aa576750864a69fa5f70f71c32 +Subproject commit 5716d69690ce21cc7653d8d8d33c0604e155d43b From git at git.haskell.org Wed Jul 26 11:49:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 11:49:40 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: Try using https url (1840207) Message-ID: <20170726114940.6F2043A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/184020739f0dda48fa4f3a3a65f58f6dd710d369/ghc >--------------------------------------------------------------- commit 184020739f0dda48fa4f3a3a65f58f6dd710d369 Author: Matthew Pickering Date: Wed Jul 26 11:49:27 2017 +0000 Try using https url >--------------------------------------------------------------- 184020739f0dda48fa4f3a3a65f58f6dd710d369 .gitmodules | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitmodules b/.gitmodules index b6513e4..4e25108 100644 --- a/.gitmodules +++ b/.gitmodules @@ -104,7 +104,7 @@ ignore = none [submodule "utils/haddock"] path = utils/haddock - url = git at github.com:mpickering/haddock.git + url = https://github.com/mpickering/haddock.git ignore = none branch = wip/T14005 [submodule "nofib"] From git at git.haskell.org Wed Jul 26 14:10:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 14:10:21 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #11672 in typecheck/should_fail/T11672. (a3f7a4f) Message-ID: <20170726141021.E7E8D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/a3f7a4f7166219b40a73133328880d52b3fc6184/ghc >--------------------------------------------------------------- commit a3f7a4f7166219b40a73133328880d52b3fc6184 Author: Richard Eisenberg Date: Thu Jun 1 18:28:57 2017 -0400 Test #11672 in typecheck/should_fail/T11672. I believe this was fixed with the fix for #11198. >--------------------------------------------------------------- a3f7a4f7166219b40a73133328880d52b3fc6184 testsuite/tests/typecheck/should_fail/T11672.hs | 9 +++++++++ testsuite/tests/typecheck/should_fail/T11672.stderr | 21 +++++++++++++++++++++ testsuite/tests/typecheck/should_fail/all.T | 2 ++ 3 files changed, 32 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T11672.hs b/testsuite/tests/typecheck/should_fail/T11672.hs new file mode 100644 index 0000000..8c5e2fb --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T11672.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE KindSignatures #-} +module BadError where + +import GHC.TypeLits +import Data.Proxy + +f :: Proxy (a :: Symbol) -> Int +f _ = f (Proxy :: Proxy (Int -> Bool)) diff --git a/testsuite/tests/typecheck/should_fail/T11672.stderr b/testsuite/tests/typecheck/should_fail/T11672.stderr new file mode 100644 index 0000000..d08acba --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T11672.stderr @@ -0,0 +1,21 @@ + +T11672.hs:9:10: error: + • Couldn't match kind ‘Symbol’ with ‘*’ + When matching types + a0 :: Symbol + Int -> Bool :: * + Expected type: Proxy a0 + Actual type: Proxy (Int -> Bool) + • In the first argument of ‘f’, namely + ‘(Proxy :: Proxy (Int -> Bool))’ + In the expression: f (Proxy :: Proxy (Int -> Bool)) + In an equation for ‘f’: f _ = f (Proxy :: Proxy (Int -> Bool)) + +T11672.hs:9:10: error: + • Couldn't match type ‘*’ with ‘Symbol’ + Expected type: Proxy a0 + Actual type: Proxy (Int -> Bool) + • In the first argument of ‘f’, namely + ‘(Proxy :: Proxy (Int -> Bool))’ + In the expression: f (Proxy :: Proxy (Int -> Bool)) + In an equation for ‘f’: f _ = f (Proxy :: Proxy (Int -> Bool)) diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 06789ed..4a1d748 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -449,3 +449,5 @@ test('T13983', normal, compile_fail, ['']) test('T13530', normal, compile_fail, ['']) test('T12373', normal, compile_fail, ['']) test('T13610', normal, compile_fail, ['']) +test('T11672', normal, compile_fail, ['']) + From git at git.haskell.org Wed Jul 26 14:10:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 14:10:28 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #11400, #11560 by documenting an infelicity. (37a52c3) Message-ID: <20170726141028.C4DEC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/37a52c36db10d68460f14d86ac2da9a45e091726/ghc >--------------------------------------------------------------- commit 37a52c36db10d68460f14d86ac2da9a45e091726 Author: Richard Eisenberg Date: Thu Jun 1 18:09:05 2017 -0400 Fix #11400, #11560 by documenting an infelicity. Really, the fix for both of these is #11307. >--------------------------------------------------------------- 37a52c36db10d68460f14d86ac2da9a45e091726 docs/users_guide/glasgow_exts.rst | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index a2cc0ba..7fc075a 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -8347,9 +8347,9 @@ enabled). The only way ``*`` is unordinary is in its parsing. In order to be backward compatible, ``*`` is parsed as if it were an alphanumeric idenfifier; note that we do not write ``Int :: (*)`` but just plain ``Int :: *``. Due to the -bizarreness with which ``*`` is parsed-and the fact that it is the only such -operator in GHC-there are some corner cases that are -not handled. We are aware of two: +bizarreness with which ``*`` is parsed--and the fact that it is the only such +operator in GHC--there are some corner cases that are +not handled. We are aware of three: - In a Haskell-98-style data constructor, you must put parentheses around ``*``, like this: :: @@ -8363,6 +8363,10 @@ not handled. We are aware of two: Note that the keyword ``type`` there is just to disambiguate the import from a term-level ``(*)``. (:ref:`explicit-namespaces`) +- In an instance declaration head (the part after the word ``instance``), you + must parenthesize ``*``. This applies to all manners of instances, including + the left-hand sides of individual equations of a closed type family. + The ``Data.Kind`` module also exports ``Type`` as a synonym for ``*``. Now that type synonyms work in kinds, it is conceivable that we will deprecate ``*`` when there is a good migration story for everyone to use ``Type``. From git at git.haskell.org Wed Jul 26 14:10:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 14:10:31 +0000 (UTC) Subject: [commit: ghc] wip/rae: Don't tidy vars when dumping a type (535eebe) Message-ID: <20170726141031.879793A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/535eebee733a71a0d1deaa611e79a6e4cf8ee476/ghc >--------------------------------------------------------------- commit 535eebee733a71a0d1deaa611e79a6e4cf8ee476 Author: Richard Eisenberg Date: Fri Apr 7 11:13:32 2017 -0400 Don't tidy vars when dumping a type This makes variables print more consistenty in, say, -ddump-tc-trace. >--------------------------------------------------------------- 535eebee733a71a0d1deaa611e79a6e4cf8ee476 compiler/types/TyCoRep.hs | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index f5d3374..9b82ab8 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -137,8 +137,8 @@ import {-# SOURCE #-} DataCon( dataConFullSig , dataConUnivTyVarBinders, dataConExTyVarBinders , DataCon, filterEqSpec ) import {-# SOURCE #-} Type( isPredTy, isCoercionTy, mkAppTy, mkCastTy - , tyCoVarsOfTypesWellScoped , tyCoVarsOfTypeWellScoped + , tyCoVarsOfTypesWellScoped , coreView, typeKind ) -- Transitively pulls in a LOT of stuff, better to break the loop @@ -2445,7 +2445,7 @@ pprType = pprPrecType TopPrec pprParendType = pprPrecType TyConPrec pprPrecType :: TyPrec -> Type -> SDoc -pprPrecType prec ty = pprPrecIfaceType prec (tidyToIfaceType ty) +pprPrecType prec ty = getPprStyle $ \sty -> pprPrecIfaceType prec (tidyToIfaceTypeSty ty sty) pprTyLit :: TyLit -> SDoc pprTyLit = pprIfaceTyLit . toIfaceTyLit @@ -2454,6 +2454,12 @@ pprKind, pprParendKind :: Kind -> SDoc pprKind = pprType pprParendKind = pprParendType +tidyToIfaceTypeSty :: Type -> PprStyle -> IfaceType +tidyToIfaceTypeSty ty sty + | userStyle sty = tidyToIfaceType ty + | otherwise = toIfaceTypeX (tyCoVarsOfType ty) ty + -- in latter case, don't tidy, as we'll be printing uniques. + tidyToIfaceType :: Type -> IfaceType -- It's vital to tidy before converting to an IfaceType -- or nested binders will become indistinguishable! From git at git.haskell.org Wed Jul 26 14:10:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 14:10:25 +0000 (UTC) Subject: [commit: ghc] wip/rae: Improve error messages around kind mismatches. (5836e65) Message-ID: <20170726141025.E53143A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/5836e6504c4e4bee65d514a64c1f47ed353a74dd/ghc >--------------------------------------------------------------- commit 5836e6504c4e4bee65d514a64c1f47ed353a74dd Author: Richard Eisenberg Date: Thu Jun 1 17:27:14 2017 -0400 Improve error messages around kind mismatches. Previously, when canonicalizing (or unifying, in uType) a heterogeneous equality, we emitted a kind equality and used the resulting coercion to cast one side of the heterogeneous equality. While sound, this led to terrible error messages. (See the bugs listed below.) The problem is that using the coercion built from the emitted kind equality is a bit like a wanted rewriting a wanted. The solution is to keep heterogeneous equalities as irreducible. See Note [Equalities with incompatible kinds] in TcCanonical. This commit also removes a highly suspicious switch to FM_SubstOnly when flattening in the kinds of a type variable. I have no idea why this was there, other than as a holdover from pre-TypeInType. I've not left a Note because there is simply no reason I can conceive of that the FM_SubstOnly should be there. One challenge with this patch is that the emitted derived equalities might get emitted several times: when a heterogeneous equality is in an implication and then gets floated out from the implication, the Derived is present both in and out of the implication. This causes a duplicate error message. (Test case: typecheck/should_fail/T7368) Solution: track the provenance of Derived constraints and refuse to float out a constraint that has an insoluble Derived. Lastly, this labels one test (dependent/should_fail/RAE_T32a) as expect_broken, because the problem is really #12919. The different handling of constraints in this patch exposes the error. This fixes bugs #11198, #12373, #13530, and #13610. test cases: typecheck/should_fail/{T8262,T8603,tcail122,T12373,T13530,T13610} >--------------------------------------------------------------- 5836e6504c4e4bee65d514a64c1f47ed353a74dd compiler/typecheck/TcCanonical.hs | 296 ++++++++++++--------- compiler/typecheck/TcErrors.hs | 75 ++++-- compiler/typecheck/TcEvidence.hs | 8 +- compiler/typecheck/TcFlatten.hs | 31 ++- compiler/typecheck/TcRnTypes.hs | 30 ++- compiler/typecheck/TcSimplify.hs | 34 ++- compiler/typecheck/TcType.hs | 10 +- compiler/typecheck/TcUnify.hs | 28 +- compiler/types/Type.hs | 4 +- testsuite/tests/dependent/should_fail/T11471.hs | 2 +- .../tests/dependent/should_fail/T11471.stderr | 11 +- testsuite/tests/dependent/should_fail/all.T | 2 +- testsuite/tests/gadt/gadt7.stderr | 6 +- .../tests/ghci.debugger/scripts/break012.stdout | 14 +- .../indexed-types/should_fail/ExtraTcsUntch.stderr | 6 +- .../tests/indexed-types/should_fail/T5934.stderr | 13 - testsuite/tests/polykinds/T12593.stderr | 56 ++++ testsuite/tests/polykinds/T13555.stderr | 21 +- testsuite/tests/polykinds/T7438.stderr | 6 +- testsuite/tests/polykinds/T8566.stderr | 2 +- testsuite/tests/polykinds/T9017.stderr | 10 +- testsuite/tests/typecheck/should_fail/T12373.hs | 10 + .../tests/typecheck/should_fail/T12373.stderr | 8 + testsuite/tests/typecheck/should_fail/T13530.hs | 11 + .../tests/typecheck/should_fail/T13530.stderr | 7 + testsuite/tests/typecheck/should_fail/T13610.hs | 11 + .../tests/typecheck/should_fail/T13610.stderr | 14 + testsuite/tests/typecheck/should_fail/T5691.stderr | 10 +- testsuite/tests/typecheck/should_fail/T7368.stderr | 6 +- .../tests/typecheck/should_fail/T7368a.stderr | 2 +- testsuite/tests/typecheck/should_fail/T7453.stderr | 48 +--- testsuite/tests/typecheck/should_fail/T7696.stderr | 4 +- testsuite/tests/typecheck/should_fail/T8262.stderr | 6 +- testsuite/tests/typecheck/should_fail/T8603.hs | 4 + testsuite/tests/typecheck/should_fail/T8603.stderr | 13 +- testsuite/tests/typecheck/should_fail/all.T | 3 + .../tests/typecheck/should_fail/tcfail090.stderr | 4 +- .../tests/typecheck/should_fail/tcfail122.stderr | 8 +- .../tests/typecheck/should_fail/tcfail123.stderr | 13 +- .../tests/typecheck/should_fail/tcfail200.stderr | 6 +- 40 files changed, 537 insertions(+), 316 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 5836e6504c4e4bee65d514a64c1f47ed353a74dd From git at git.haskell.org Wed Jul 26 14:10:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 14:10:34 +0000 (UTC) Subject: [commit: ghc] wip/rae: Remove old coercion pretty-printer (3596cbc) Message-ID: <20170726141034.5AE8A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/3596cbc19df9a8a23d9ea8ed35ff89ebdc4270b3/ghc >--------------------------------------------------------------- commit 3596cbc19df9a8a23d9ea8ed35ff89ebdc4270b3 Author: Richard Eisenberg Date: Tue Jun 6 11:01:14 2017 -0400 Remove old coercion pretty-printer Now, all coercions are printed from IfaceType, just like types. This also changes the rendering of TransCo to use ; instead of a prefix operator. >--------------------------------------------------------------- 3596cbc19df9a8a23d9ea8ed35ff89ebdc4270b3 compiler/iface/IfaceType.hs | 3 +- compiler/iface/ToIface.hs | 4 +- compiler/iface/ToIface.hs-boot | 2 +- compiler/types/Coercion.hs | 107 +++++----------------------------------- compiler/types/Coercion.hs-boot | 3 -- compiler/types/TyCoRep.hs | 35 ++++++++++--- compiler/types/Type.hs | 2 +- compiler/types/Type.hs-boot | 7 +-- 8 files changed, 49 insertions(+), 114 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 3596cbc19df9a8a23d9ea8ed35ff89ebdc4270b3 From git at git.haskell.org Wed Jul 26 14:10:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 14:10:37 +0000 (UTC) Subject: [commit: ghc] wip/rae: Preserve CoVar uniques during pretty printing (8bc86db) Message-ID: <20170726141037.188393A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/8bc86dbb2fd6c3e8da3f1ff26609f4d4d403de50/ghc >--------------------------------------------------------------- commit 8bc86dbb2fd6c3e8da3f1ff26609f4d4d403de50 Author: Richard Eisenberg Date: Tue Jun 6 10:07:16 2017 -0400 Preserve CoVar uniques during pretty printing Previously, we did this for Types, but not for Coercions. >--------------------------------------------------------------- 8bc86dbb2fd6c3e8da3f1ff26609f4d4d403de50 compiler/backpack/RnModIface.hs | 1 + compiler/iface/IfaceSyn.hs | 1 + compiler/iface/IfaceType.hs | 9 ++++++++- compiler/iface/TcIface.hs | 1 + compiler/iface/ToIface.hs | 8 +++++--- testsuite/tests/roles/should_compile/Roles13.stderr | 2 +- 6 files changed, 17 insertions(+), 5 deletions(-) diff --git a/compiler/backpack/RnModIface.hs b/compiler/backpack/RnModIface.hs index 2e738c1..e3da067 100644 --- a/compiler/backpack/RnModIface.hs +++ b/compiler/backpack/RnModIface.hs @@ -646,6 +646,7 @@ rnIfaceCo (IfaceAppCo co1 co2) = IfaceAppCo <$> rnIfaceCo co1 <*> rnIfaceCo co2 rnIfaceCo (IfaceForAllCo bndr co1 co2) = IfaceForAllCo <$> rnIfaceTvBndr bndr <*> rnIfaceCo co1 <*> rnIfaceCo co2 +rnIfaceCo (IfaceFreeCoVar c) = pure (IfaceFreeCoVar c) rnIfaceCo (IfaceCoVarCo lcl) = IfaceCoVarCo <$> pure lcl rnIfaceCo (IfaceAxiomInstCo n i cs) = IfaceAxiomInstCo <$> rnIfaceGlobal n <*> pure i <*> mapM rnIfaceCo cs diff --git a/compiler/iface/IfaceSyn.hs b/compiler/iface/IfaceSyn.hs index 60206ea..3360d74 100644 --- a/compiler/iface/IfaceSyn.hs +++ b/compiler/iface/IfaceSyn.hs @@ -1424,6 +1424,7 @@ freeNamesIfCoercion (IfaceAppCo c1 c2) = freeNamesIfCoercion c1 &&& freeNamesIfCoercion c2 freeNamesIfCoercion (IfaceForAllCo _ kind_co co) = freeNamesIfCoercion kind_co &&& freeNamesIfCoercion co +freeNamesIfCoercion (IfaceFreeCoVar _) = emptyNameSet freeNamesIfCoercion (IfaceCoVarCo _) = emptyNameSet freeNamesIfCoercion (IfaceAxiomInstCo ax _ cos) diff --git a/compiler/iface/IfaceType.hs b/compiler/iface/IfaceType.hs index 39e3028..4ab40d4 100644 --- a/compiler/iface/IfaceType.hs +++ b/compiler/iface/IfaceType.hs @@ -109,7 +109,7 @@ data IfaceOneShot -- See Note [Preserve OneShotInfo] in CoreTicy type IfaceKind = IfaceType data IfaceType -- A kind of universal type, used for types and kinds - = IfaceFreeTyVar TyVar -- See Note [Free tyvars in IfaceType] + = IfaceFreeTyVar TyVar -- See Note [Free tyvars in IfaceType] | IfaceTyVar IfLclName -- Type/coercion variable only, not tycon | IfaceLitTy IfaceTyLit | IfaceAppTy IfaceType IfaceType @@ -204,6 +204,7 @@ Note that: to deserialise one. IfaceFreeTyVar is used only in the "convert to IfaceType and then pretty-print" pipeline. +We do the same for covars, naturally. Note [Equality predicates in IfaceType] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -242,6 +243,7 @@ data IfaceCoercion | IfaceTyConAppCo Role IfaceTyCon [IfaceCoercion] | IfaceAppCo IfaceCoercion IfaceCoercion | IfaceForAllCo IfaceTvBndr IfaceCoercion IfaceCoercion + | IfaceFreeCoVar CoVar -- See Note [Free tyvars in IfaceType] | IfaceCoVarCo IfLclName | IfaceAxiomInstCo IfExtName BranchIndex [IfaceCoercion] | IfaceUnivCo IfaceUnivCoProv Role IfaceType IfaceType @@ -395,6 +397,7 @@ substIfaceType env ty go_co (IfaceTyConAppCo r tc cos) = IfaceTyConAppCo r tc (go_cos cos) go_co (IfaceAppCo c1 c2) = IfaceAppCo (go_co c1) (go_co c2) go_co (IfaceForAllCo {}) = pprPanic "substIfaceCoercion" (ppr ty) + go_co (IfaceFreeCoVar cv) = IfaceFreeCoVar cv go_co (IfaceCoVarCo cv) = IfaceCoVarCo cv go_co (IfaceAxiomInstCo a i cos) = IfaceAxiomInstCo a i (go_cos cos) go_co (IfaceUnivCo prov r t1 t2) = IfaceUnivCo (go_prov prov) r (go t1) (go t2) @@ -1039,6 +1042,8 @@ ppr_co ctxt_prec co@(IfaceForAllCo {}) = let (tvs, co'') = split_co co' in ((name,kind_co):tvs,co'') split_co co' = ([], co') +-- Why these two? See Note [TcTyVars in IfaceType] +ppr_co _ (IfaceFreeCoVar covar) = ppr covar ppr_co _ (IfaceCoVarCo covar) = ppr covar ppr_co ctxt_prec (IfaceUnivCo IfaceUnsafeCoerceProv r ty1 ty2) @@ -1321,6 +1326,8 @@ instance Binary IfaceCoercion where put_ bh a put_ bh b put_ bh c + put_ _ (IfaceFreeCoVar cv) + = pprPanic "Can't serialise IfaceFreeCoVar" (ppr cv) put_ bh (IfaceCoVarCo a) = do putByte bh 6 put_ bh a diff --git a/compiler/iface/TcIface.hs b/compiler/iface/TcIface.hs index 418994d..b3119b2 100644 --- a/compiler/iface/TcIface.hs +++ b/compiler/iface/TcIface.hs @@ -1321,6 +1321,7 @@ tcIfaceCo = go go (IfaceForAllCo tv k c) = do { k' <- go k ; bindIfaceTyVar tv $ \ tv' -> ForAllCo tv' k' <$> go c } + go (IfaceFreeCoVar c) = pprPanic "tcIfaceCo:IfaceFreeCoVar" (ppr c) go (IfaceCoVarCo n) = CoVarCo <$> go_var n go (IfaceAxiomInstCo n i cs) = AxiomInstCo <$> tcIfaceCoAxiom n <*> pure i <*> mapM go cs go (IfaceUnivCo p r t1 t2) = UnivCo <$> tcIfaceUnivCoProv p <*> pure r diff --git a/compiler/iface/ToIface.hs b/compiler/iface/ToIface.hs index 6f2acba..d4a2115 100644 --- a/compiler/iface/ToIface.hs +++ b/compiler/iface/ToIface.hs @@ -217,7 +217,10 @@ toIfaceCoercionX fr co = go co where go (Refl r ty) = IfaceReflCo r (toIfaceType ty) - go (CoVarCo cv) = IfaceCoVarCo (toIfaceCoVar cv) + go (CoVarCo cv) + -- See [TcTyVars in IfaceType] in IfaceType + | cv `elemVarSet` fr = IfaceFreeCoVar cv + | otherwise = IfaceCoVarCo (toIfaceCoVar cv) go (AppCo co1 co2) = IfaceAppCo (go co1) (go co2) go (SymCo co) = IfaceSymCo (go co) go (TransCo co1 co2) = IfaceTransCo (go co1) (go co2) @@ -236,8 +239,7 @@ toIfaceCoercionX fr co | tc `hasKey` funTyConKey , [_,_,_,_] <- cos = pprPanic "toIfaceCoercion" (ppr co) | otherwise = IfaceTyConAppCo r (toIfaceTyCon tc) (map go cos) - go (FunCo r co1 co2) = IfaceFunCo r (toIfaceCoercion co1) - (toIfaceCoercion co2) + go (FunCo r co1 co2) = IfaceFunCo r (go co1) (go co2) go (ForAllCo tv k co) = IfaceForAllCo (toIfaceTvBndr tv) (toIfaceCoercionX fr' k) diff --git a/testsuite/tests/roles/should_compile/Roles13.stderr b/testsuite/tests/roles/should_compile/Roles13.stderr index f4b44a2..414ef80 100644 --- a/testsuite/tests/roles/should_compile/Roles13.stderr +++ b/testsuite/tests/roles/should_compile/Roles13.stderr @@ -13,7 +13,7 @@ convert :: Wrap Age -> Int [GblId, Arity=1, Caf=NoCafRefs] convert = convert1 - `cast` (_R -> Roles13.N:Wrap[0] Roles13.N:Age[0] + `cast` (_R ->_R Roles13.N:Wrap[0] (Roles13.N:Age[0]) :: (Wrap Age -> Wrap Age :: *) ~R# (Wrap Age -> Int :: *)) -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} From git at git.haskell.org Wed Jul 26 14:10:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 14:10:40 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #12369 by being more flexible with data insts (1cf0827) Message-ID: <20170726141040.57AD63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/1cf0827fc8b93f3c77daebf630d77f56660dbb6f/ghc >--------------------------------------------------------------- commit 1cf0827fc8b93f3c77daebf630d77f56660dbb6f Author: Richard Eisenberg Date: Wed Jul 19 12:28:04 2017 -0400 Fix #12369 by being more flexible with data insts Previously, a data family's kind had to end in `Type`, and data instances had to list all the type patterns for the family. However, both of these restrictions were unnecessary: - A data family's kind can usefully end in a kind variable `k`. See examples on #12369. - A data instance need not list all patterns, much like how a GADT-style data declaration need not list all type parameters, when a kind signature is in place. This is useful, for example, here: data family Sing (a :: k) data instance Sing :: Bool -> Type where ... This patch also improved a few error messages, as some error plumbing had to be moved around. See new Note [Arity of data families] in FamInstEnv for more info. test case: indexed-types/should_compile/T12369 >--------------------------------------------------------------- 1cf0827fc8b93f3c77daebf630d77f56660dbb6f compiler/typecheck/TcHsSyn.hs | 2 +- compiler/typecheck/TcHsType.hs | 175 ++++++++------- compiler/typecheck/TcInstDcls.hs | 25 ++- compiler/typecheck/TcTyClsDecls.hs | 239 ++++++++++++++++----- compiler/typecheck/TcValidity.hs | 42 ++-- compiler/types/FamInstEnv.hs | 43 +++- compiler/types/TyCon.hs | 10 +- compiler/types/Type.hs | 2 +- docs/users_guide/8.4.1-notes.rst | 6 + docs/users_guide/glasgow_exts.rst | 5 + .../tests/indexed-types/should_compile/T12369.hs | 35 +++ testsuite/tests/indexed-types/should_compile/all.T | 1 + .../indexed-types/should_fail/ExtraTcsUntch.stderr | 6 +- .../indexed-types/should_fail/Overlap4.stderr | 8 +- .../indexed-types/should_fail/SimpleFail1b.stderr | 8 +- .../indexed-types/should_fail/TyFamArity1.stderr | 8 +- .../indexed-types/should_fail/TyFamArity2.stderr | 9 +- 17 files changed, 415 insertions(+), 209 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 1cf0827fc8b93f3c77daebf630d77f56660dbb6f From git at git.haskell.org Wed Jul 26 14:10:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 14:10:43 +0000 (UTC) Subject: [commit: ghc] wip/rae: Document that type holes kill polymorphic recursion (1076173) Message-ID: <20170726141043.155213A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/10761735d742f4af76058a2cf7e0fe98952a0190/ghc >--------------------------------------------------------------- commit 10761735d742f4af76058a2cf7e0fe98952a0190 Author: Richard Eisenberg Date: Tue Jul 18 15:55:21 2017 -0400 Document that type holes kill polymorphic recursion This "fixes" #11995. >--------------------------------------------------------------- 10761735d742f4af76058a2cf7e0fe98952a0190 docs/users_guide/glasgow_exts.rst | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 7fc075a..b0da2891 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -10290,6 +10290,10 @@ warnings instead of errors. Additionally, these warnings can be silenced with the :ghc-flag:`-Wno-partial-type-signatures <-Wpartial-type-signatures>` flag. +However, because GHC must *infer* the type when part of a type is left +out, it is unable to use polymorphic recursion. The same restriction +takes place when the type signature is omitted completely. + .. _pts-syntax: Syntax From git at git.haskell.org Wed Jul 26 14:10:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 14:10:45 +0000 (UTC) Subject: [commit: ghc] wip/rae: Track visibility in TypeEqOrigin (6b78773) Message-ID: <20170726141045.D38153A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/6b78773929bbbed5a021b67bcdaef23f545c07eb/ghc >--------------------------------------------------------------- commit 6b78773929bbbed5a021b67bcdaef23f545c07eb Author: Richard Eisenberg Date: Tue Jul 18 14:30:40 2017 -0400 Track visibility in TypeEqOrigin A type equality error can arise from a mismatch between *invisible* arguments just as easily as from visible arguments. But we should really prefer printing out errors from visible arguments over invisible ones. Suppose we have a mismatch between `Proxy Int` and `Proxy Maybe`. Would you rather get an error between `Int` and `Maybe`? Or between `*` and `* -> *`? I thought so, too. There is a fair amount of plumbing with this one, but I think it's worth it. >--------------------------------------------------------------- 6b78773929bbbed5a021b67bcdaef23f545c07eb compiler/typecheck/Inst.hs | 3 +- compiler/typecheck/TcCanonical.hs | 18 +++-- compiler/typecheck/TcErrors.hs | 29 ++++---- compiler/typecheck/TcHsType.hs | 5 +- compiler/typecheck/TcRnTypes.hs | 30 ++++++++- compiler/typecheck/TcType.hs | 38 ++++++++++- compiler/typecheck/TcUnify.hs | 78 +++++++++++++--------- testsuite/tests/polykinds/KindVType.stderr | 2 +- .../tests/typecheck/should_fail/T12373.stderr | 3 + .../tests/typecheck/should_fail/T13530.stderr | 3 + testsuite/tests/typecheck/should_fail/T8603.stderr | 7 +- 11 files changed, 150 insertions(+), 66 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 6b78773929bbbed5a021b67bcdaef23f545c07eb From git at git.haskell.org Wed Jul 26 14:10:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 14:10:48 +0000 (UTC) Subject: [commit: ghc] wip/rae: Refactor tcInferApps. (ee3a6f3) Message-ID: <20170726141048.954293A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/ee3a6f31389b3d141fa8d19f5e229b019078a025/ghc >--------------------------------------------------------------- commit ee3a6f31389b3d141fa8d19f5e229b019078a025 Author: Richard Eisenberg Date: Mon Jul 24 15:49:00 2017 -0400 Refactor tcInferApps. With the changes caused by the fix to #12369, it is now clearer how to rewrite tcInferApps and friends. This should change no behavior, but it does clean up a nasty corner of the type checker. This commit also removes some uses of substTyUnchecked. >--------------------------------------------------------------- ee3a6f31389b3d141fa8d19f5e229b019078a025 compiler/typecheck/TcHsType.hs | 115 +++++++++++++++++++++-------------------- compiler/types/TyCoRep.hs | 10 ++-- compiler/types/Type.hs | 2 +- 3 files changed, 64 insertions(+), 63 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 ee3a6f31389b3d141fa8d19f5e229b019078a025 From git at git.haskell.org Wed Jul 26 14:10:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 14:10:51 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #11963 by checking for more mixed type/kinds (e77ccd1) Message-ID: <20170726141051.CFE1E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/e77ccd195c0ff5d997949ace7c789112caf8d2ff/ghc >--------------------------------------------------------------- commit e77ccd195c0ff5d997949ace7c789112caf8d2ff Author: Richard Eisenberg Date: Tue Jul 18 15:49:38 2017 -0400 Fix #11963 by checking for more mixed type/kinds This is a straightforward fix -- there were just some omitted checks. test case: typecheck/should_fail/T11963 >--------------------------------------------------------------- e77ccd195c0ff5d997949ace7c789112caf8d2ff compiler/rename/RnTypes.hs | 25 +++++++++++++++---- testsuite/tests/typecheck/should_fail/T11963.hs | 29 ++++++++++++++++++++++ .../tests/typecheck/should_fail/T11963.stderr | 20 +++++++++++++++ testsuite/tests/typecheck/should_fail/all.T | 2 +- 4 files changed, 70 insertions(+), 6 deletions(-) diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs index 014d485..a0ceb32 100644 --- a/compiler/rename/RnTypes.hs +++ b/compiler/rename/RnTypes.hs @@ -1717,11 +1717,25 @@ extract_hs_tv_bndrs tvs = do { FKTV bndr_kvs _ <- foldrM extract_lkind emptyFKTV [k | L _ (KindedTyVar _ k) <- tvs] - ; let locals = map hsLTyVarName tvs + ; let locals = map hsLTyVarLocName tvs + + -- These checks are all tested in typecheck/should_fail/T11963 + ; check_for_mixed_vars bndr_kvs acc_tvs + ; check_for_mixed_vars bndr_kvs body_tvs + ; check_for_mixed_vars body_tvs acc_kvs + ; check_for_mixed_vars body_kvs acc_tvs + ; check_for_mixed_vars locals body_kvs + ; return $ - FKTV (filterOut ((`elem` locals) . unLoc) (bndr_kvs ++ body_kvs) + FKTV (filterOut (`elemRdr` locals) (bndr_kvs ++ body_kvs) ++ acc_kvs) - (filterOut ((`elem` locals) . unLoc) body_tvs ++ acc_tvs) } + (filterOut (`elemRdr` locals) body_tvs ++ acc_tvs) } + where + check_for_mixed_vars :: [Located RdrName] -> [Located RdrName] -> RnM () + check_for_mixed_vars tvs1 tvs2 = mapM_ check tvs1 + where + check tv1 = when (isRdrTyVar (unLoc tv1) && (tv1 `elemRdr` tvs2)) $ + mixedVarsErr tv1 extract_tv :: TypeOrKind -> Located RdrName -> FreeKiTyVars -> RnM FreeKiTyVars @@ -1737,8 +1751,6 @@ extract_tv t_or_k ltv@(L _ tv) acc mixedVarsErr ltv ; return (FKTV (ltv : kvs) tvs) } | otherwise = return acc - where - elemRdr x = any (eqLocated x) mixedVarsErr :: Located RdrName -> RnM () mixedVarsErr (L loc tv) @@ -1751,3 +1763,6 @@ mixedVarsErr (L loc tv) -- just used in this module; seemed convenient here nubL :: Eq a => [Located a] -> [Located a] nubL = nubBy eqLocated + +elemRdr :: Located RdrName -> [Located RdrName] -> Bool +elemRdr x = any (eqLocated x) diff --git a/testsuite/tests/typecheck/should_fail/T11963.hs b/testsuite/tests/typecheck/should_fail/T11963.hs new file mode 100644 index 0000000..c4f78ae --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T11963.hs @@ -0,0 +1,29 @@ +{-# LANGUAGE GADTs, PolyKinds, RankNTypes #-} + +module T11963 where + +-- this module should be rejected without TypeInType + +import Data.Proxy + +-- see code in RnTypes.extract_hs_tv_bndrs which checks for these bad cases + + -- bndr_kvs vs body_tvs +data Typ k t where + Typ :: (forall (a :: k -> *). a t -> a t) -> Typ k t + + -- bndr_kvs vs acc_tvs +foo :: (forall (t :: k). Proxy t) -> Proxy k +foo _ = undefined + + -- locals vs body_kvs +bar :: forall k. forall (t :: k). Proxy t +bar = undefined + + -- body_kvs vs acc_tvs +quux :: (forall t. Proxy (t :: k)) -> Proxy k +quux _ = undefined + + -- body_tvs vs acc_kvs +blargh :: (forall a. a -> Proxy k) -> Proxy (t :: k) +blargh _ = undefined diff --git a/testsuite/tests/typecheck/should_fail/T11963.stderr b/testsuite/tests/typecheck/should_fail/T11963.stderr new file mode 100644 index 0000000..74c3ab0 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T11963.stderr @@ -0,0 +1,20 @@ + +T11963.hs:13:26: error: + Variable ‘k’ used as both a kind and a type + Did you intend to use TypeInType? + +T11963.hs:16:22: error: + Variable ‘k’ used as both a kind and a type + Did you intend to use TypeInType? + +T11963.hs:20:15: error: + Variable ‘k’ used as both a kind and a type + Did you intend to use TypeInType? + +T11963.hs:24:32: error: + Variable ‘k’ used as both a kind and a type + Did you intend to use TypeInType? + +T11963.hs:28:33: error: + Variable ‘k’ used as both a kind and a type + Did you intend to use TypeInType? diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 58ae57f..3d2a595 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -451,4 +451,4 @@ test('T12373', normal, compile_fail, ['']) test('T13610', normal, compile_fail, ['']) test('T11672', normal, compile_fail, ['']) test('T13819', normal, compile_fail, ['']) - +test('T11963', normal, compile_fail, ['']) From git at git.haskell.org Wed Jul 26 14:10:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 14:10:55 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #12176 by being a bit more careful instantiating. (8c89c94) Message-ID: <20170726141055.14FBE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/8c89c947c5626ebf18fc501912b6c6c9ffdb2f3c/ghc >--------------------------------------------------------------- commit 8c89c947c5626ebf18fc501912b6c6c9ffdb2f3c Author: Richard Eisenberg Date: Tue Jul 18 19:44:17 2017 -0400 Fix #12176 by being a bit more careful instantiating. Previously, looking up a TyCon that said "no" to mightBeUnsaturated would then instantiate all of its invisible binders. But this is wrong for vanilla type synonyms, whose RHS kind might legitimately start with invisible binders. So a little more care is taken now, only to instantiate those invisible binders that need to be (so that the TyCon isn't unsaturated). >--------------------------------------------------------------- 8c89c947c5626ebf18fc501912b6c6c9ffdb2f3c compiler/typecheck/TcCanonical.hs | 4 +- compiler/typecheck/TcHsType.hs | 50 ++++++++++++++-------- testsuite/tests/dependent/should_compile/T12176.hs | 18 ++++++++ testsuite/tests/dependent/should_compile/all.T | 1 + 4 files changed, 53 insertions(+), 20 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 23de0e5..48c1bec 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -24,7 +24,7 @@ import FamInstEnv ( FamInstEnvs ) import FamInst ( tcTopNormaliseNewTypeTF_maybe ) import Var import VarEnv( mkInScopeSet ) -import VarSet( extendVarSetList ) +import VarSet import Outputable import DynFlags( DynFlags ) import NameSet @@ -683,7 +683,7 @@ can_eq_nc_forall ev eq_rel s1 s2 go _ _ _ = panic "cna_eq_nc_forall" -- case (s:ss) [] empty_subst2 = mkEmptyTCvSubst $ mkInScopeSet $ - free_tvs2 `extendVarSetList` skol_tvs + free_tvs2 `unionVarSet` closeOverKinds (mkVarSet skol_tvs) ; (implic, _ev_binds, all_co) <- buildImplication skol_info skol_tvs [] $ go skol_tvs empty_subst2 bndrs2 diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 185c034..01c9adb 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -922,30 +922,42 @@ checkExpectedKind hs_ty ty act_kind exp_kind , TcKind ) -- its new kind instantiate ty act_ki exp_ki = let (exp_bndrs, _) = splitPiTysInvisible exp_ki in - instantiateTyN (length exp_bndrs) ty act_ki - --- | Instantiate a type to have at most @n@ invisible arguments. -instantiateTyN :: Int -- ^ @n@ - -> TcType -- ^ the type - -> TcKind -- ^ its kind - -> TcM (TcType, TcKind) -- ^ The inst'ed type with kind -instantiateTyN n ty ki - = let (bndrs, inner_ki) = splitPiTysInvisible ki - num_to_inst = length bndrs - n - -- NB: splitAt is forgiving with invalid numbers - (inst_bndrs, leftover_bndrs) = splitAt num_to_inst bndrs + instantiateTyUntilN (length exp_bndrs) ty act_ki + +-- | Instantiate @n@ invisible arguments to a type. If @n <= 0@, no instantiation +-- occurs. If @n@ is too big, then all available invisible arguments are instantiated. +-- (In other words, this function is very forgiving about bad values of @n at .) +instantiateTyN :: Int -- ^ @n@ + -> TcType -- ^ the type + -> [TyBinder] -> TcKind -- ^ its kind + -> TcM (TcType, TcKind) -- ^ The inst'ed type with kind +instantiateTyN n ty bndrs inner_ki + = let -- NB: splitAt is forgiving with invalid numbers + (inst_bndrs, leftover_bndrs) = splitAt n bndrs + ki = mkPiTys bndrs inner_ki empty_subst = mkEmptyTCvSubst (mkInScopeSet (tyCoVarsOfType ki)) in - if num_to_inst <= 0 then return (ty, ki) else + if n <= 0 then return (ty, ki) else do { (subst, inst_args) <- tcInstBinders empty_subst Nothing inst_bndrs ; let rebuilt_ki = mkPiTys leftover_bndrs inner_ki ki' = substTy subst rebuilt_ki ; traceTc "instantiateTyN" (vcat [ ppr ty <+> dcolon <+> ppr ki + , ppr n , ppr subst , ppr rebuilt_ki , ppr ki' ]) ; return (mkNakedAppTys ty inst_args, ki') } +-- | Instantiate a type to have at most @n@ invisible arguments. +instantiateTyUntilN :: Int -- ^ @n@ + -> TcType -- ^ the type + -> TcKind -- ^ its kind + -> TcM (TcType, TcKind) -- ^ The inst'ed type with kind +instantiateTyUntilN n ty ki + = let (bndrs, inner_ki) = splitPiTysInvisible ki + num_to_inst = length bndrs - n + in + instantiateTyN num_to_inst ty bndrs inner_ki --------------------------- tcHsContext :: LHsContext GhcRn -> TcM [PredType] @@ -1018,8 +1030,8 @@ tcTyVar mode name -- Could be a tyvar, a tycon, or a datacon -- if we are type-checking a type family tycon, we must instantiate -- any invisible arguments right away. Otherwise, we get #11246 - handle_tyfams :: TyCon -- the tycon to instantiate (might be loopy) - -> TyCon -- a non-loopy version of the tycon + handle_tyfams :: TyCon -- the tycon to instantiate (might be loopy) + -> TcTyCon -- a non-loopy version of the tycon -> TcM (TcType, TcKind) handle_tyfams tc tc_tc | mightBeUnsaturatedTyCon tc_tc @@ -1027,7 +1039,8 @@ tcTyVar mode name -- Could be a tyvar, a tycon, or a datacon ; return (ty, tc_kind) } | otherwise - = do { (tc_ty, kind) <- instantiateTyN 0 ty tc_kind + = do { (tc_ty, kind) <- instantiateTyN (length (tyConBinders tc_tc)) + ty tc_kind_bndrs tc_inner_ki -- tc and tc_ty must not be traced here, because that would -- force the evaluation of a potentially knot-tied variable (tc), -- and the typechecker would hang, as per #11708 @@ -1035,8 +1048,9 @@ tcTyVar mode name -- Could be a tyvar, a tycon, or a datacon , ppr kind ]) ; return (tc_ty, kind) } where - ty = mkNakedTyConApp tc [] - tc_kind = tyConKind tc_tc + ty = mkNakedTyConApp tc [] + tc_kind = tyConKind tc_tc + (tc_kind_bndrs, tc_inner_ki) = splitPiTysInvisible tc_kind get_loopy_tc :: Name -> TyCon -> TcM TyCon -- Return the knot-tied global TyCon if there is one diff --git a/testsuite/tests/dependent/should_compile/T12176.hs b/testsuite/tests/dependent/should_compile/T12176.hs new file mode 100644 index 0000000..0e34006 --- /dev/null +++ b/testsuite/tests/dependent/should_compile/T12176.hs @@ -0,0 +1,18 @@ +{-# LANGUAGE RankNTypes, TypeInType, GADTs, TypeFamilies #-} + +module T12176 where + +import Data.Kind + +data Proxy :: forall k. k -> Type where + MkProxy :: forall k (a :: k). Proxy a + +data X where + MkX :: forall (k :: Type) (a :: k). Proxy a -> X + +type Expr = (MkX :: forall (a :: Bool). Proxy a -> X) + +type family Foo (x :: forall (a :: k). Proxy a -> X) where + Foo (MkX :: forall (a :: k). Proxy a -> X) = (MkProxy :: Proxy k) + +type Bug = Foo Expr -- this failed with #12176 diff --git a/testsuite/tests/dependent/should_compile/all.T b/testsuite/tests/dependent/should_compile/all.T index 8a9b221..b854f1d 100644 --- a/testsuite/tests/dependent/should_compile/all.T +++ b/testsuite/tests/dependent/should_compile/all.T @@ -24,3 +24,4 @@ test('T11719', normal, compile, ['']) test('T11966', normal, compile, ['']) test('T12442', normal, compile, ['']) test('T13538', normal, compile, ['']) +test('T12176', normal, compile, ['']) From git at git.haskell.org Wed Jul 26 14:10:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 14:10:59 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #13819 by refactoring TypeEqOrigin.uo_thing (c95db6e) Message-ID: <20170726141059.051613A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/c95db6e6ee8d9cb339e58bb82235fdafbc9ee056/ghc >--------------------------------------------------------------- commit c95db6e6ee8d9cb339e58bb82235fdafbc9ee056 Author: Richard Eisenberg Date: Wed Jun 14 16:35:18 2017 -0400 Fix #13819 by refactoring TypeEqOrigin.uo_thing The uo_thing field of TypeEqOrigin is used to track the "thing" (either term or type) that has the type (kind) stored in the TypeEqOrigin fields. Previously, this was sometimes a proper Core Type, which needed zonking and tidying. Now, it is only HsSyn: much simpler, and the error messages now use the user-written syntax. But this aspect of uo_thing didn't cause #13819; it was the sibling field uo_arity that did. uo_arity stored the number of arguments of uo_thing, useful when reporting something like "should have written 2 fewer arguments". We wouldn't want to say that if the thing didn't have two arguments. However, in practice, GHC was getting this wrong, and this message didn't seem all that helpful. Furthermore, the calculation of the number of arguments is what caused #13819 to fall over. This patch just removes uo_arity. In my opinion, the change to error messages is a nudge in the right direction. Test case: typecheck/should_fail/T13819 >--------------------------------------------------------------- c95db6e6ee8d9cb339e58bb82235fdafbc9ee056 compiler/ghci/RtClosureInspect.hs | 4 +- compiler/typecheck/Inst.hs | 8 +- compiler/typecheck/TcArrows.hs | 2 +- compiler/typecheck/TcErrors.hs | 20 ++- compiler/typecheck/TcExpr.hs | 50 ++++---- compiler/typecheck/TcHsType.hs | 135 +++++++++++---------- compiler/typecheck/TcMType.hs | 30 +---- compiler/typecheck/TcPat.hs | 6 +- compiler/typecheck/TcRnTypes.hs | 21 +--- compiler/typecheck/TcSigs.hs | 4 +- compiler/typecheck/TcSplice.hs | 13 +- compiler/typecheck/TcSplice.hs-boot | 6 +- compiler/typecheck/TcTyClsDecls.hs | 2 +- compiler/typecheck/TcType.hs | 7 ++ compiler/typecheck/TcUnify.hs | 65 +++++----- compiler/typecheck/TcUnify.hs-boot | 7 +- compiler/types/Type.hs | 2 +- .../tests/indexed-types/should_fail/T12867.stderr | 3 +- testsuite/tests/polykinds/T12593.stderr | 7 +- testsuite/tests/polykinds/T6039.stderr | 3 +- testsuite/tests/polykinds/T7278.stderr | 3 +- testsuite/tests/polykinds/T8616.stderr | 2 +- testsuite/tests/polykinds/T9200b.stderr | 6 +- .../tests/rename/should_fail/rnfail026.stderr | 3 +- testsuite/tests/th/T3177a.stderr | 6 +- .../tests/typecheck/should_fail/T11356.stderr | 3 +- .../tests/typecheck/should_fail/T11672.stderr | 11 +- .../tests/typecheck/should_fail/T12785b.stderr | 6 + testsuite/tests/typecheck/should_fail/T13819.hs | 14 +++ .../tests/typecheck/should_fail/T13819.stderr | 18 +++ testsuite/tests/typecheck/should_fail/T2994.stderr | 3 +- testsuite/tests/typecheck/should_fail/T3540.stderr | 2 +- testsuite/tests/typecheck/should_fail/T4875.stderr | 6 +- testsuite/tests/typecheck/should_fail/T7609.stderr | 11 +- testsuite/tests/typecheck/should_fail/T7778.stderr | 10 +- testsuite/tests/typecheck/should_fail/all.T | 1 + .../tests/typecheck/should_fail/tcfail070.stderr | 3 +- .../tests/typecheck/should_fail/tcfail078.stderr | 6 +- .../tests/typecheck/should_fail/tcfail113.stderr | 12 +- .../tests/typecheck/should_fail/tcfail123.stderr | 9 -- .../tests/typecheck/should_fail/tcfail132.stderr | 3 +- 41 files changed, 243 insertions(+), 290 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 c95db6e6ee8d9cb339e58bb82235fdafbc9ee056 From git at git.haskell.org Wed Jul 26 14:11:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 14:11:01 +0000 (UTC) Subject: [commit: ghc] wip/rae's head updated: Refactor tcInferApps. (ee3a6f3) Message-ID: <20170726141101.7363A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/rae' now includes: 6ab3c5f Typeable: Always use UTF-8 string unpacking primitive d7b1751 configure: Cleanup ARM COPY bug test artifacts a051b55 testsuite: Ensure that hs_try_putmvar003 terminates c9e4c86 Allow visible type application for [] 1ed41a7 Fix links to SPJ’s papers (fixes #12578) 0b89b2d Add Haddocks for Eq (STRef a) and Eq (IORef a) c940e3b dmdAnal: Ensure that ExnStr flag isn't dropped inappropriately 6e3c901 Fix #13983 by creating a TyConFlavour type, and using it 927e781 typo: -XUndeci[d]ableInstances b066d93 base: Improve docs to clarify when finalizers may not be run cc839c5 Typeable: Ensure that promoted data family instance tycons get bindings a273c73 Spelling fixes eeb141d Demand: Improve comments 8e51bfc Introduce -fcatch-bottoms c9c762d testsuite: Pipe stdin directly to process a85a595 arcconfig: Set project ruleset to use master merge-base by default 194384f Fix busy-wait in SysTools.builderMainLoop fdb6a5b Make IfaceAxiom typechecking lazier. 5469ac8 Interpreter.c: use macros to access/modify Sp bade356 rts: Claim AP_STACK before adjusting Sp 1480080 distrib/configure: Canonicalize triples b2d3ec3 testsuite: Add test for #13916 ccac387 Revert "testsuite: Add test for #13916" 36e8bcb HsPat: Assume that no spliced patterns are irrefutable fefcbfa build system: Ensure there are no duplicate files in bindist list acbbb50 Fix ungrammatical error message cbbf083 fix dllwrap issue. c1d9690 Avoid linear lookup in unload_wkr in the Linker ee1047e Update autoconf scripts 98ab12a distrib/configure: Carry FFI include/lib paths from source distribution fb08252 users-guide: Improve legibility of OverlappingInstances documentation 0ae0f46 Preserve HaskellHaveRTSLinker in bindist 646ec0e Bump a bunch of submodules b8afdaf Update release notes for 8.2.1 fb17cc5 Bump integer-gmp version ecc9e9a ghc-prim: Bump version d4e9721 testsuite: Fix cabal01 for real this time 44b090b users-guide: Standardize and repair all flag references c945195 users-guide: Fix various wibbles 2dff2c7 Fix more documentation wibbles 145f1c7 Remove 8.0.2 release notes file 88f20bd Add a caveat to the GHC.Generics examples about :+: nesting a602b65 users-guides: Fix errant whitespace 0c04d78 users-guide: Cross-reference more flags 58b62d6 users-guide: Eliminate some redundant index entries 3e5d0f1 users-guide: Make it easier to reference haddocks 897366a users-guide: Fix URL of deferred type errors paper 85a295d ghc-prim: Don't allocate a thunk for each unpacked UTF-8 character 8a8cee7 DynFlags: Drop rtsBuildTag field d8051c6 Use libpthread instead of libthr on FreeBSD 8ec7770 testsuite: Add testcase for #13168 2183ac1 Fix import error with -XPackageImports when the module has a duplicate name 58545fd base: Introduce GHC.ByteOrder 104c72b Expose FrontendPluginAction 7d1909a Remove unused language pragma 36b270a Revert "Remove unused language pragma" 6bb32ba Fix #10684 by processing deriving clauses with finer grain 746ab0b Add an Outputable instance for ListMap 75bf11c Fix binder visiblity for default methods 6386fc3 Comments and tc-tracing only f959624 Comments only d31181b Test Trac #14033 5836e65 Improve error messages around kind mismatches. 37a52c3 Fix #11400, #11560 by documenting an infelicity. a3f7a4f Test #11672 in typecheck/should_fail/T11672. 535eebe Don't tidy vars when dumping a type 8bc86db Preserve CoVar uniques during pretty printing 3596cbc Remove old coercion pretty-printer c95db6e Fix #13819 by refactoring TypeEqOrigin.uo_thing 6b78773 Track visibility in TypeEqOrigin e77ccd1 Fix #11963 by checking for more mixed type/kinds 1076173 Document that type holes kill polymorphic recursion 8c89c94 Fix #12176 by being a bit more careful instantiating. 1cf0827 Fix #12369 by being more flexible with data insts ee3a6f3 Refactor tcInferApps. From git at git.haskell.org Wed Jul 26 14:40:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 14:40:32 +0000 (UTC) Subject: [commit: ghc] master: Fix note references and some typos (362339d) Message-ID: <20170726144032.B7C873A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/362339dd4cfd652b63c7cd1b7ea5a7486bb40944/ghc >--------------------------------------------------------------- commit 362339dd4cfd652b63c7cd1b7ea5a7486bb40944 Author: Gabor Greif Date: Wed Jul 26 15:13:04 2017 +0200 Fix note references and some typos >--------------------------------------------------------------- 362339dd4cfd652b63c7cd1b7ea5a7486bb40944 compiler/llvmGen/Llvm/AbsSyn.hs | 4 ++-- compiler/llvmGen/Llvm/PpLlvm.hs | 2 +- compiler/nativeGen/RegAlloc/Graph/Spill.hs | 2 +- compiler/prelude/primops.txt.pp | 2 +- compiler/specialise/Specialise.hs | 2 +- compiler/typecheck/TcDerivInfer.hs | 2 +- compiler/typecheck/TcRnTypes.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 6 +++--- rts/ProfHeap.c | 2 +- rts/RaiseAsync.c | 2 +- rts/RetainerSet.h | 2 +- testsuite/tests/programs/galois_raytrace/Eval.hs | 2 +- 12 files changed, 15 insertions(+), 15 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 362339dd4cfd652b63c7cd1b7ea5a7486bb40944 From git at git.haskell.org Wed Jul 26 16:42:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 16:42:49 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: More refined annotations + binders + bindings (48889bc) Message-ID: <20170726164249.EEE163A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/48889bcd2371facda52e01bd7a7017c57bbe8159/ghc >--------------------------------------------------------------- commit 48889bcd2371facda52e01bd7a7017c57bbe8159 Author: Matthew Pickering Date: Wed Jul 26 16:42:23 2017 +0000 More refined annotations + binders + bindings >--------------------------------------------------------------- 48889bcd2371facda52e01bd7a7017c57bbe8159 compiler/coreSyn/PprCore.hs | 19 ++++++++++--------- compiler/utils/OutputableAnnotation.hs | 16 ++++++++++++++-- 2 files changed, 24 insertions(+), 11 deletions(-) diff --git a/compiler/coreSyn/PprCore.hs b/compiler/coreSyn/PprCore.hs index da78d1e..a77b593 100644 --- a/compiler/coreSyn/PprCore.hs +++ b/compiler/coreSyn/PprCore.hs @@ -67,7 +67,7 @@ instance OutputableBndr b => Outputable (Expr b) where ppr expr = pprCoreExpr expr pprCoreBindingsWithAnn :: [CoreBind] -> SDoc -pprCoreBindingsWithAnn = pprTopBinds realAnn +pprCoreBindingsWithAnn = pprTopBinds noAnn {- ************************************************************************ @@ -99,8 +99,8 @@ pprTopBinds :: OutputableBndr a pprTopBinds ann binds = vcat (map (pprTopBind ann) binds) pprTopBind :: OutputableBndr a => Annotation a -> Bind a -> SDoc -pprTopBind ann (NonRec binder expr) - = ppr_binding ann (binder,expr) $$ blankLine +pprTopBind ann b@(NonRec binder expr) + = addAnn (PBind b) (ppr_binding ann (binder,expr)) $$ blankLine pprTopBind _ (Rec []) = text "Rec { }" @@ -120,13 +120,14 @@ ppr_bind ann (Rec binds) = vcat (map pp binds) ppr_binding :: OutputableBndr b => Annotation b -> (b, Expr b) -> SDoc ppr_binding ann (val_bdr, expr) - = ann expr $$ pprBndr LetBind val_bdr $$ pp_bind + = ann expr $$ (pprBndr LetBind val_bdr) $$ pp_bind where pp_bind = case bndrIsJoin_maybe val_bdr of Nothing -> pp_normal_bind Just ar -> pp_join_bind ar - pp_normal_bind = hang (ppr val_bdr) 2 (equals <+> pprCoreExpr expr) + pp_normal_bind = hang (ppr val_bdr) 2 (equals <+> + addAnn (PCoreExpr expr) (pprCoreExpr expr)) -- For a join point of join arity n, we want to print j = \x1 ... xn -> e -- as "j x1 ... xn = e" to differentiate when a join point returns a @@ -134,7 +135,7 @@ ppr_binding ann (val_bdr, expr) -- an n-argument function). pp_join_bind join_arity = hang (ppr val_bdr <+> sep (map (pprBndr LambdaBind) lhs_bndrs)) - 2 (equals <+> pprCoreExpr rhs) + 2 (equals <+> (addAnn (PCoreExpr expr) (pprCoreExpr rhs))) where (lhs_bndrs, rhs) = collectNBinders join_arity expr @@ -348,9 +349,9 @@ binders are printed as "_". -- These instances are sadly orphans instance OutputableBndr Var where - pprBndr = pprCoreBinder - pprInfixOcc = pprInfixName . varName - pprPrefixOcc = pprPrefixName . varName + pprBndr bs b = addAnn (varBinder b) (pprCoreBinder bs b) + pprInfixOcc b = addAnn (varReference b) (pprInfixName (varName b)) + pprPrefixOcc b = addAnn (varReference b) (pprPrefixName (varName b)) bndrIsJoin_maybe = isJoinId_maybe instance Outputable b => OutputableBndr (TaggedBndr b) where diff --git a/compiler/utils/OutputableAnnotation.hs b/compiler/utils/OutputableAnnotation.hs index f506a0b..1ad2d83 100644 --- a/compiler/utils/OutputableAnnotation.hs +++ b/compiler/utils/OutputableAnnotation.hs @@ -1,9 +1,21 @@ {-# LANGUAGE GADTs #-} -module OutputableAnnotation (PExpr(..)) where +module OutputableAnnotation (PExpr(..), BindType, varBinder, varReference) where import CoreSyn +import Outputable ( OutputableBndr(..)) data PExpr where - PCoreExpr :: CoreExpr -> PExpr + PCoreExpr :: OutputableBndr a => Expr a -> PExpr + PBind :: OutputableBndr a => Bind a -> PExpr + PVar :: OutputableBndr a => BindType -> a -> PExpr + +data BindType = Binder | Reference + +varBinder :: OutputableBndr a => a -> PExpr +varBinder a = PVar Binder a + +varReference :: OutputableBndr a => a -> PExpr +varReference a = PVar Reference a + From git at git.haskell.org Wed Jul 26 21:17:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 21:17:51 +0000 (UTC) Subject: [commit: ghc] master: Fix #13968 by consulting isBuiltInOcc_maybe (d774b4e) Message-ID: <20170726211751.D72903A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d774b4e2de4f07d2432b67010305fede7aeefc78/ghc >--------------------------------------------------------------- commit d774b4e2de4f07d2432b67010305fede7aeefc78 Author: Ryan Scott Date: Wed Jul 26 17:13:57 2017 -0400 Fix #13968 by consulting isBuiltInOcc_maybe Summary: We were unconditionally reporting `Illegal binding of built-in syntax` in an error message, but this error doesn't make sense in certain Template Haskell scenarios which can trigger it. Let's give a more sensible error message by first checking if the name we're binding really is built-in syntax, using the handy `isBuiltInOcc_maybe` function. Test Plan: make test TEST=T13968 Reviewers: bgamari, austin, goldfire Reviewed By: goldfire Subscribers: goldfire, rwbarton, thomie GHC Trac Issues: #13968 Differential Revision: https://phabricator.haskell.org/D3789 >--------------------------------------------------------------- d774b4e2de4f07d2432b67010305fede7aeefc78 compiler/rename/RnEnv.hs | 18 +++++++++++++++--- testsuite/tests/th/T13968.hs | 6 ++++++ testsuite/tests/th/T13968.stderr | 3 +++ testsuite/tests/th/all.T | 1 + 4 files changed, 25 insertions(+), 3 deletions(-) diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs index 617b355..298de54 100644 --- a/compiler/rename/RnEnv.hs +++ b/compiler/rename/RnEnv.hs @@ -53,7 +53,7 @@ import HscTypes import TcEnv import TcRnMonad import RdrHsSyn ( setRdrNameSpace ) -import TysWiredIn ( starKindTyConName, unicodeStarKindTyConName ) +import TysWiredIn import Name import NameSet import NameEnv @@ -1573,5 +1573,17 @@ opDeclErr n badOrigBinding :: RdrName -> SDoc badOrigBinding name - = text "Illegal binding of built-in syntax:" <+> ppr (rdrNameOcc name) - -- The rdrNameOcc is because we don't want to print Prelude.(,) + | Just _ <- isBuiltInOcc_maybe occ + = text "Illegal binding of built-in syntax:" <+> ppr occ + -- Use an OccName here because we don't want to print Prelude.(,) + | otherwise + = text "Cannot redefine a Name retrieved by a Template Haskell quote:" + <+> ppr name + -- This can happen when one tries to use a Template Haskell splice to + -- define a top-level identifier with an already existing name, e.g., + -- + -- $(pure [ValD (VarP 'succ) (NormalB (ConE 'True)) []]) + -- + -- (See Trac #13968.) + where + occ = rdrNameOcc name diff --git a/testsuite/tests/th/T13968.hs b/testsuite/tests/th/T13968.hs new file mode 100644 index 0000000..1e54ef1 --- /dev/null +++ b/testsuite/tests/th/T13968.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE TemplateHaskell #-} +module T13968 where + +import Language.Haskell.TH + +$(pure [ValD (VarP 'succ) (NormalB (ConE 'True)) []]) diff --git a/testsuite/tests/th/T13968.stderr b/testsuite/tests/th/T13968.stderr new file mode 100644 index 0000000..2850dae --- /dev/null +++ b/testsuite/tests/th/T13968.stderr @@ -0,0 +1,3 @@ + +T13968.hs:6:3: error: + Cannot redefine a Name retrieved by a Template Haskell quote: succ diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index f89be6e..df31162 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -390,3 +390,4 @@ test('T13642', normal, compile_fail, ['-v0']) test('T13781', normal, compile, ['-v0']) test('T13782', normal, compile, ['']) test('T13856', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques']) +test('T13968', normal, compile_fail, ['-v0']) From git at git.haskell.org Wed Jul 26 22:40:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Jul 2017 22:40:13 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: Some more references and actually export binder type (36b8478) Message-ID: <20170726224013.052ED3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/36b847896360d4e9b7ae86b4b1e664b8af476d2b/ghc >--------------------------------------------------------------- commit 36b847896360d4e9b7ae86b4b1e664b8af476d2b Author: Matthew Pickering Date: Wed Jul 26 22:38:52 2017 +0000 Some more references and actually export binder type Need to do some refinement about where definition sites are printed but this will do for now. >--------------------------------------------------------------- 36b847896360d4e9b7ae86b4b1e664b8af476d2b compiler/coreSyn/PprCore.hs | 4 ++-- compiler/utils/OutputableAnnotation.hs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/coreSyn/PprCore.hs b/compiler/coreSyn/PprCore.hs index a77b593..70ae2e1 100644 --- a/compiler/coreSyn/PprCore.hs +++ b/compiler/coreSyn/PprCore.hs @@ -158,7 +158,7 @@ ppr_expr :: OutputableBndr b => (SDoc -> SDoc) -> Expr b -> SDoc ppr_expr add_par (Var name) | isJoinId name = add_par ((text "jump") <+> ppr name) - | otherwise = ppr name + | otherwise = addAnn (varReference name) (ppr name) ppr_expr add_par (Type ty) = add_par (text "TYPE:" <+> ppr ty) -- Weird ppr_expr add_par (Coercion co) = add_par (text "CO:" <+> ppr co) ppr_expr add_par (Lit lit) = pprLiteral add_par lit @@ -202,7 +202,7 @@ ppr_expr add_par expr@(App {}) _ -> parens (hang fun_doc 2 pp_args) where fun_doc | isJoinId f = text "jump" <+> ppr f - | otherwise = ppr f + | otherwise = addAnn (varReference f) (ppr f) _ -> parens (hang (pprParendExpr fun) 2 pp_args) } diff --git a/compiler/utils/OutputableAnnotation.hs b/compiler/utils/OutputableAnnotation.hs index 1ad2d83..71b9c69 100644 --- a/compiler/utils/OutputableAnnotation.hs +++ b/compiler/utils/OutputableAnnotation.hs @@ -1,5 +1,5 @@ {-# LANGUAGE GADTs #-} -module OutputableAnnotation (PExpr(..), BindType, varBinder, varReference) where +module OutputableAnnotation (PExpr(..), BindType(..), varBinder, varReference) where import CoreSyn import Outputable ( OutputableBndr(..)) From git at git.haskell.org Thu Jul 27 01:29:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 01:29:03 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Fixing the patch to only include relevant bits. (a4bfe98) Message-ID: <20170727012903.8E78E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/a4bfe98fd30e31c9b02a12ac0c6d8b49efec8c16/ghc >--------------------------------------------------------------- commit a4bfe98fd30e31c9b02a12ac0c6d8b49efec8c16 Author: Jared Weakly Date: Wed Jul 26 12:53:33 2017 -0700 Fixing the patch to only include relevant bits. >--------------------------------------------------------------- a4bfe98fd30e31c9b02a12ac0c6d8b49efec8c16 testsuite/driver/perf_notes.py | 105 +++++++++++++---------------------------- 1 file changed, 34 insertions(+), 71 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 a4bfe98fd30e31c9b02a12ac0c6d8b49efec8c16 From git at git.haskell.org Thu Jul 27 01:29:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 01:29:06 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Merge branch 'wip/perf-testsuite' of git.haskell.org:ghc into wip/perf-testsuite Splitting commits (4005835) Message-ID: <20170727012906.53F533A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/4005835d1bd04a41ace3bcede1be01ee6a0e2bf6/ghc >--------------------------------------------------------------- commit 4005835d1bd04a41ace3bcede1be01ee6a0e2bf6 Merge: a4bfe98 809165b Author: Jared Weakly Date: Wed Jul 26 13:34:55 2017 -0700 Merge branch 'wip/perf-testsuite' of git.haskell.org:ghc into wip/perf-testsuite Splitting commits >--------------------------------------------------------------- 4005835d1bd04a41ace3bcede1be01ee6a0e2bf6 From git at git.haskell.org Thu Jul 27 01:29:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 01:29:11 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Greatly improved printing. Fixed the delta function. Made things simpler (6dee76d) Message-ID: <20170727012911.D842A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/6dee76d026cd0d441dbac69c4bc2baa90b4f7842/ghc >--------------------------------------------------------------- commit 6dee76d026cd0d441dbac69c4bc2baa90b4f7842 Author: Jared Weakly Date: Wed Jul 26 18:30:37 2017 -0700 Greatly improved printing. Fixed the delta function. Made things simpler Signed-off-by: Jared Weakly >--------------------------------------------------------------- 6dee76d026cd0d441dbac69c4bc2baa90b4f7842 testsuite/driver/perf_notes.py | 104 +++++++++++++++++++---------------------- testsuite/driver/testutil.py | 9 ++-- 2 files changed, 51 insertions(+), 62 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 6dee76d026cd0d441dbac69c4bc2baa90b4f7842 From git at git.haskell.org Thu Jul 27 01:29:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 01:29:09 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: This should actually split things out this time (67ad19a) Message-ID: <20170727012909.0F2523A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/67ad19a71f0b7fe82f573ca8b7c929bd25a3ecb5/ghc >--------------------------------------------------------------- commit 67ad19a71f0b7fe82f573ca8b7c929bd25a3ecb5 Author: Jared Weakly Date: Wed Jul 26 13:52:07 2017 -0700 This should actually split things out this time >--------------------------------------------------------------- 67ad19a71f0b7fe82f573ca8b7c929bd25a3ecb5 testsuite/driver/runtests.py | 24 ------------------------ 1 file changed, 24 deletions(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index 1893ddc..d9e98d4 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -6,7 +6,6 @@ from __future__ import print_function -import argparse import signal import sys import os @@ -42,24 +41,6 @@ def signal_handler(signal, frame): # ----------------------------------------------------------------------------- # cmd-line options -# argparse implementation -# parser = argparse.ArgumentParser() -# parser.add_argument("configfile=", help="config file") -# parser.add_argument("config=", help="config field") -# parser.add_argument("rootdir=", help="root of tree containing tests (default: .)") -# parser.add_argument("summary-file=", help="file in which to save the (human-readable) summary") -# parser.add_argument("no-print-summary=", help="should we print the summary?") -# parser.add_argument("only=", help="just this test (can be give multiple --only= flags)") -# parser.add_argument("way=", help="just this way") -# parser.add_argument("skipway=", help="skip this way") -# parser.add_argument("threads=", help="threads to run simultaneously") -# parser.add_argument("check-files-written", help="check files aren't written by multiple tests") -# parser.add_argument("verbose=", help="verbose (0,1,2 so far)") -# parser.add_argument("skip-perf-tests", help="skip performance tests") -# parser.add_argument("only-perf-tests", help="Only do performance tests") -# parser.add_argument("use-git-notes", help="use git notes to store metrics. NOTE: This is expected to become the default and will eventually be taken out.") -# parser.add_argument("test-env=", help="Override default chosen test-env.") - long_options = [ "configfile=", # config file "config=", # config field @@ -79,11 +60,6 @@ long_options = [ ] opts, args = getopt.getopt(sys.argv[1:], "e:", long_options) -# argparse implementation -# aargs = parser.parse_args() - -# if aargs.configfile: -# exec(open(aarg.configfile)) for opt,arg in opts: if opt == '--configfile': From git at git.haskell.org Thu Jul 27 09:55:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 09:55:49 +0000 (UTC) Subject: [commit: ghc] wip/annotate-core: Use NamedThing rather than just outputablebndr (1a9aae8) Message-ID: <20170727095549.C7A673A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/annotate-core Link : http://ghc.haskell.org/trac/ghc/changeset/1a9aae88ec8f57393db4992748a7de08c54cfe61/ghc >--------------------------------------------------------------- commit 1a9aae88ec8f57393db4992748a7de08c54cfe61 Author: Matthew Pickering Date: Thu Jul 27 09:55:21 2017 +0000 Use NamedThing rather than just outputablebndr >--------------------------------------------------------------- 1a9aae88ec8f57393db4992748a7de08c54cfe61 compiler/coreSyn/CoreSyn.hs | 3 +++ compiler/coreSyn/PprCore.hs | 30 +++++++++++++++--------------- compiler/utils/OutputableAnnotation.hs | 11 ++++++----- 3 files changed, 24 insertions(+), 20 deletions(-) diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs index 41202c3..230c7f2 100644 --- a/compiler/coreSyn/CoreSyn.hs +++ b/compiler/coreSyn/CoreSyn.hs @@ -1762,6 +1762,9 @@ type TaggedAlt t = Alt (TaggedBndr t) instance Outputable b => Outputable (TaggedBndr b) where ppr (TB b l) = char '<' <> ppr b <> comma <> ppr l <> char '>' +instance NamedThing (TaggedBndr b) where + getName (TB v _) = getName v + deTagExpr :: TaggedExpr t -> CoreExpr deTagExpr (Var v) = Var v deTagExpr (Lit l) = Lit l diff --git a/compiler/coreSyn/PprCore.hs b/compiler/coreSyn/PprCore.hs index 70ae2e1..d4ae498 100644 --- a/compiler/coreSyn/PprCore.hs +++ b/compiler/coreSyn/PprCore.hs @@ -18,7 +18,7 @@ module PprCore ( import CoreSyn import CoreStats (exprStats) import Literal( pprLiteral ) -import Name( pprInfixName, pprPrefixName ) +import Name( pprInfixName, pprPrefixName, NamedThing) import Var import Id import IdInfo @@ -46,10 +46,10 @@ import SrcLoc ( pprUserRealSpan ) @pprParendCoreExpr@ puts parens around non-atomic Core expressions. -} -pprCoreBindings :: OutputableBndr b => [Bind b] -> SDoc -pprCoreBinding :: OutputableBndr b => Bind b -> SDoc -pprCoreExpr :: OutputableBndr b => Expr b -> SDoc -pprParendExpr :: OutputableBndr b => Expr b -> SDoc +pprCoreBindings :: (OutputableBndr b, NamedThing b) => [Bind b] -> SDoc +pprCoreBinding :: (OutputableBndr b, NamedThing b) => Bind b -> SDoc +pprCoreExpr :: (OutputableBndr b, NamedThing b) => Expr b -> SDoc +pprParendExpr :: (OutputableBndr b, NamedThing b) => Expr b -> SDoc pprCoreBindings = pprTopBinds noAnn pprCoreBinding = pprTopBind noAnn @@ -60,10 +60,10 @@ pprCoreBindingWithSize :: CoreBind -> SDoc pprCoreBindingsWithSize = pprTopBinds sizeAnn pprCoreBindingWithSize = pprTopBind sizeAnn -instance OutputableBndr b => Outputable (Bind b) where +instance (OutputableBndr b, NamedThing b) => Outputable (Bind b) where ppr bind = ppr_bind noAnn bind -instance OutputableBndr b => Outputable (Expr b) where +instance (OutputableBndr b, NamedThing b) => Outputable (Expr b) where ppr expr = pprCoreExpr expr pprCoreBindingsWithAnn :: [CoreBind] -> SDoc @@ -91,14 +91,14 @@ realAnn e = addAnn (PCoreExpr e) (ppr e) noAnn :: Expr b -> SDoc noAnn _ = empty -pprTopBinds :: OutputableBndr a +pprTopBinds :: (OutputableBndr a, NamedThing a) => Annotation a -- ^ generate an annotation to place before the -- binding -> [Bind a] -- ^ bindings to show -> SDoc -- ^ the pretty result pprTopBinds ann binds = vcat (map (pprTopBind ann) binds) -pprTopBind :: OutputableBndr a => Annotation a -> Bind a -> SDoc +pprTopBind :: (OutputableBndr a, NamedThing a) => Annotation a -> Bind a -> SDoc pprTopBind ann b@(NonRec binder expr) = addAnn (PBind b) (ppr_binding ann (binder,expr)) $$ blankLine @@ -111,14 +111,14 @@ pprTopBind ann (Rec (b:bs)) text "end Rec }", blankLine] -ppr_bind :: OutputableBndr b => Annotation b -> Bind b -> SDoc +ppr_bind :: (OutputableBndr b, NamedThing b) => Annotation b -> Bind b -> SDoc ppr_bind ann (NonRec val_bdr expr) = ppr_binding ann (val_bdr, expr) ppr_bind ann (Rec binds) = vcat (map pp binds) where pp bind = ppr_binding ann bind <> semi -ppr_binding :: OutputableBndr b => Annotation b -> (b, Expr b) -> SDoc +ppr_binding :: (OutputableBndr b, NamedThing b) => Annotation b -> (b, Expr b) -> SDoc ppr_binding ann (val_bdr, expr) = ann expr $$ (pprBndr LetBind val_bdr) $$ pp_bind where @@ -152,7 +152,7 @@ pprOptCo co = sdocWithDynFlags $ \dflags -> then angleBrackets (text "Co:" <> int (coercionSize co)) else parens (sep [ppr co, dcolon <+> ppr (coercionType co)]) -ppr_expr :: OutputableBndr b => (SDoc -> SDoc) -> Expr b -> SDoc +ppr_expr :: (OutputableBndr b, NamedThing b) => (SDoc -> SDoc) -> Expr b -> SDoc -- The function adds parens in context that need -- an atomic value (e.g. function args) @@ -287,11 +287,11 @@ ppr_expr add_par (Tick tickish expr) then ppr_expr add_par expr else add_par (sep [ppr tickish, pprCoreExpr expr]) -pprCoreAlt :: OutputableBndr a => (AltCon, [a] , Expr a) -> SDoc +pprCoreAlt :: (OutputableBndr a, NamedThing a) => (AltCon, [a] , Expr a) -> SDoc pprCoreAlt (con, args, rhs) = hang (ppr_case_pat con args <+> arrow) 2 (pprCoreExpr rhs) -ppr_case_pat :: OutputableBndr a => AltCon -> [a] -> SDoc +ppr_case_pat :: (OutputableBndr a, NamedThing a) => AltCon -> [a] -> SDoc ppr_case_pat (DataAlt dc) args | Just sort <- tyConTuple_maybe tc = tupleParens sort (pprWithCommas ppr_bndr args) @@ -306,7 +306,7 @@ ppr_case_pat con args -- | Pretty print the argument in a function application. -pprArg :: OutputableBndr a => Expr a -> SDoc +pprArg :: (OutputableBndr a, NamedThing a) => Expr a -> SDoc pprArg (Type ty) = sdocWithDynFlags $ \dflags -> if gopt Opt_SuppressTypeApplications dflags diff --git a/compiler/utils/OutputableAnnotation.hs b/compiler/utils/OutputableAnnotation.hs index 71b9c69..12a7bba 100644 --- a/compiler/utils/OutputableAnnotation.hs +++ b/compiler/utils/OutputableAnnotation.hs @@ -3,18 +3,19 @@ module OutputableAnnotation (PExpr(..), BindType(..), varBinder, varReference) w import CoreSyn import Outputable ( OutputableBndr(..)) +import Name (NamedThing) data PExpr where - PCoreExpr :: OutputableBndr a => Expr a -> PExpr - PBind :: OutputableBndr a => Bind a -> PExpr - PVar :: OutputableBndr a => BindType -> a -> PExpr + PCoreExpr :: (OutputableBndr a, NamedThing a) => Expr a -> PExpr + PBind :: (OutputableBndr a, NamedThing a) => Bind a -> PExpr + PVar :: (OutputableBndr a, NamedThing a) => BindType -> a -> PExpr data BindType = Binder | Reference -varBinder :: OutputableBndr a => a -> PExpr +varBinder :: (OutputableBndr a, NamedThing a) => a -> PExpr varBinder a = PVar Binder a -varReference :: OutputableBndr a => a -> PExpr +varReference :: (OutputableBndr a, NamedThing a) => a -> PExpr varReference a = PVar Reference a From git at git.haskell.org Thu Jul 27 11:05:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 11:05:50 +0000 (UTC) Subject: [commit: ghc] master: Remove unneeded import (4a26415) Message-ID: <20170727110550.E7FFB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4a2641578bc91707e06b2f35b0fec63535e9a025/ghc >--------------------------------------------------------------- commit 4a2641578bc91707e06b2f35b0fec63535e9a025 Author: Gabor Greif Date: Thu Jul 27 13:04:21 2017 +0200 Remove unneeded import >--------------------------------------------------------------- 4a2641578bc91707e06b2f35b0fec63535e9a025 compiler/main/Packages.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index 2c5833f..1bd2531 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -88,7 +88,6 @@ import Data.Char ( toUpper ) import Data.List as List import Data.Map (Map) import Data.Set (Set) -import Data.Maybe (mapMaybe) import Data.Monoid (First(..)) #if __GLASGOW_HASKELL__ > 710 import Data.Semigroup ( Semigroup ) From git at git.haskell.org Thu Jul 27 11:49:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 11:49:42 +0000 (UTC) Subject: [commit: ghc] master: Don't tidy vars when dumping a type (ef39af7) Message-ID: <20170727114942.9B5D63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ef39af721a9002dda5c7ea5a781d7747792f1d5f/ghc >--------------------------------------------------------------- commit ef39af721a9002dda5c7ea5a781d7747792f1d5f Author: Richard Eisenberg Date: Fri Apr 7 11:13:32 2017 -0400 Don't tidy vars when dumping a type This makes variables print more consistenty in, say, -ddump-tc-trace. >--------------------------------------------------------------- ef39af721a9002dda5c7ea5a781d7747792f1d5f compiler/types/TyCoRep.hs | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index f5d3374..9b82ab8 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -137,8 +137,8 @@ import {-# SOURCE #-} DataCon( dataConFullSig , dataConUnivTyVarBinders, dataConExTyVarBinders , DataCon, filterEqSpec ) import {-# SOURCE #-} Type( isPredTy, isCoercionTy, mkAppTy, mkCastTy - , tyCoVarsOfTypesWellScoped , tyCoVarsOfTypeWellScoped + , tyCoVarsOfTypesWellScoped , coreView, typeKind ) -- Transitively pulls in a LOT of stuff, better to break the loop @@ -2445,7 +2445,7 @@ pprType = pprPrecType TopPrec pprParendType = pprPrecType TyConPrec pprPrecType :: TyPrec -> Type -> SDoc -pprPrecType prec ty = pprPrecIfaceType prec (tidyToIfaceType ty) +pprPrecType prec ty = getPprStyle $ \sty -> pprPrecIfaceType prec (tidyToIfaceTypeSty ty sty) pprTyLit :: TyLit -> SDoc pprTyLit = pprIfaceTyLit . toIfaceTyLit @@ -2454,6 +2454,12 @@ pprKind, pprParendKind :: Kind -> SDoc pprKind = pprType pprParendKind = pprParendType +tidyToIfaceTypeSty :: Type -> PprStyle -> IfaceType +tidyToIfaceTypeSty ty sty + | userStyle sty = tidyToIfaceType ty + | otherwise = toIfaceTypeX (tyCoVarsOfType ty) ty + -- in latter case, don't tidy, as we'll be printing uniques. + tidyToIfaceType :: Type -> IfaceType -- It's vital to tidy before converting to an IfaceType -- or nested binders will become indistinguishable! From git at git.haskell.org Thu Jul 27 11:49:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 11:49:45 +0000 (UTC) Subject: [commit: ghc] master: Preserve CoVar uniques during pretty printing (bb2a446) Message-ID: <20170727114945.586843A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bb2a446ae488522489c4ce03081439659820174c/ghc >--------------------------------------------------------------- commit bb2a446ae488522489c4ce03081439659820174c Author: Richard Eisenberg Date: Tue Jun 6 10:07:16 2017 -0400 Preserve CoVar uniques during pretty printing Previously, we did this for Types, but not for Coercions. >--------------------------------------------------------------- bb2a446ae488522489c4ce03081439659820174c compiler/backpack/RnModIface.hs | 1 + compiler/iface/IfaceSyn.hs | 1 + compiler/iface/IfaceType.hs | 9 ++++++++- compiler/iface/TcIface.hs | 1 + compiler/iface/ToIface.hs | 8 +++++--- testsuite/tests/roles/should_compile/Roles13.stderr | 2 +- 6 files changed, 17 insertions(+), 5 deletions(-) diff --git a/compiler/backpack/RnModIface.hs b/compiler/backpack/RnModIface.hs index 2e738c1..e3da067 100644 --- a/compiler/backpack/RnModIface.hs +++ b/compiler/backpack/RnModIface.hs @@ -646,6 +646,7 @@ rnIfaceCo (IfaceAppCo co1 co2) = IfaceAppCo <$> rnIfaceCo co1 <*> rnIfaceCo co2 rnIfaceCo (IfaceForAllCo bndr co1 co2) = IfaceForAllCo <$> rnIfaceTvBndr bndr <*> rnIfaceCo co1 <*> rnIfaceCo co2 +rnIfaceCo (IfaceFreeCoVar c) = pure (IfaceFreeCoVar c) rnIfaceCo (IfaceCoVarCo lcl) = IfaceCoVarCo <$> pure lcl rnIfaceCo (IfaceAxiomInstCo n i cs) = IfaceAxiomInstCo <$> rnIfaceGlobal n <*> pure i <*> mapM rnIfaceCo cs diff --git a/compiler/iface/IfaceSyn.hs b/compiler/iface/IfaceSyn.hs index 60206ea..3360d74 100644 --- a/compiler/iface/IfaceSyn.hs +++ b/compiler/iface/IfaceSyn.hs @@ -1424,6 +1424,7 @@ freeNamesIfCoercion (IfaceAppCo c1 c2) = freeNamesIfCoercion c1 &&& freeNamesIfCoercion c2 freeNamesIfCoercion (IfaceForAllCo _ kind_co co) = freeNamesIfCoercion kind_co &&& freeNamesIfCoercion co +freeNamesIfCoercion (IfaceFreeCoVar _) = emptyNameSet freeNamesIfCoercion (IfaceCoVarCo _) = emptyNameSet freeNamesIfCoercion (IfaceAxiomInstCo ax _ cos) diff --git a/compiler/iface/IfaceType.hs b/compiler/iface/IfaceType.hs index 39e3028..4ab40d4 100644 --- a/compiler/iface/IfaceType.hs +++ b/compiler/iface/IfaceType.hs @@ -109,7 +109,7 @@ data IfaceOneShot -- See Note [Preserve OneShotInfo] in CoreTicy type IfaceKind = IfaceType data IfaceType -- A kind of universal type, used for types and kinds - = IfaceFreeTyVar TyVar -- See Note [Free tyvars in IfaceType] + = IfaceFreeTyVar TyVar -- See Note [Free tyvars in IfaceType] | IfaceTyVar IfLclName -- Type/coercion variable only, not tycon | IfaceLitTy IfaceTyLit | IfaceAppTy IfaceType IfaceType @@ -204,6 +204,7 @@ Note that: to deserialise one. IfaceFreeTyVar is used only in the "convert to IfaceType and then pretty-print" pipeline. +We do the same for covars, naturally. Note [Equality predicates in IfaceType] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -242,6 +243,7 @@ data IfaceCoercion | IfaceTyConAppCo Role IfaceTyCon [IfaceCoercion] | IfaceAppCo IfaceCoercion IfaceCoercion | IfaceForAllCo IfaceTvBndr IfaceCoercion IfaceCoercion + | IfaceFreeCoVar CoVar -- See Note [Free tyvars in IfaceType] | IfaceCoVarCo IfLclName | IfaceAxiomInstCo IfExtName BranchIndex [IfaceCoercion] | IfaceUnivCo IfaceUnivCoProv Role IfaceType IfaceType @@ -395,6 +397,7 @@ substIfaceType env ty go_co (IfaceTyConAppCo r tc cos) = IfaceTyConAppCo r tc (go_cos cos) go_co (IfaceAppCo c1 c2) = IfaceAppCo (go_co c1) (go_co c2) go_co (IfaceForAllCo {}) = pprPanic "substIfaceCoercion" (ppr ty) + go_co (IfaceFreeCoVar cv) = IfaceFreeCoVar cv go_co (IfaceCoVarCo cv) = IfaceCoVarCo cv go_co (IfaceAxiomInstCo a i cos) = IfaceAxiomInstCo a i (go_cos cos) go_co (IfaceUnivCo prov r t1 t2) = IfaceUnivCo (go_prov prov) r (go t1) (go t2) @@ -1039,6 +1042,8 @@ ppr_co ctxt_prec co@(IfaceForAllCo {}) = let (tvs, co'') = split_co co' in ((name,kind_co):tvs,co'') split_co co' = ([], co') +-- Why these two? See Note [TcTyVars in IfaceType] +ppr_co _ (IfaceFreeCoVar covar) = ppr covar ppr_co _ (IfaceCoVarCo covar) = ppr covar ppr_co ctxt_prec (IfaceUnivCo IfaceUnsafeCoerceProv r ty1 ty2) @@ -1321,6 +1326,8 @@ instance Binary IfaceCoercion where put_ bh a put_ bh b put_ bh c + put_ _ (IfaceFreeCoVar cv) + = pprPanic "Can't serialise IfaceFreeCoVar" (ppr cv) put_ bh (IfaceCoVarCo a) = do putByte bh 6 put_ bh a diff --git a/compiler/iface/TcIface.hs b/compiler/iface/TcIface.hs index 418994d..b3119b2 100644 --- a/compiler/iface/TcIface.hs +++ b/compiler/iface/TcIface.hs @@ -1321,6 +1321,7 @@ tcIfaceCo = go go (IfaceForAllCo tv k c) = do { k' <- go k ; bindIfaceTyVar tv $ \ tv' -> ForAllCo tv' k' <$> go c } + go (IfaceFreeCoVar c) = pprPanic "tcIfaceCo:IfaceFreeCoVar" (ppr c) go (IfaceCoVarCo n) = CoVarCo <$> go_var n go (IfaceAxiomInstCo n i cs) = AxiomInstCo <$> tcIfaceCoAxiom n <*> pure i <*> mapM go cs go (IfaceUnivCo p r t1 t2) = UnivCo <$> tcIfaceUnivCoProv p <*> pure r diff --git a/compiler/iface/ToIface.hs b/compiler/iface/ToIface.hs index 6f2acba..d4a2115 100644 --- a/compiler/iface/ToIface.hs +++ b/compiler/iface/ToIface.hs @@ -217,7 +217,10 @@ toIfaceCoercionX fr co = go co where go (Refl r ty) = IfaceReflCo r (toIfaceType ty) - go (CoVarCo cv) = IfaceCoVarCo (toIfaceCoVar cv) + go (CoVarCo cv) + -- See [TcTyVars in IfaceType] in IfaceType + | cv `elemVarSet` fr = IfaceFreeCoVar cv + | otherwise = IfaceCoVarCo (toIfaceCoVar cv) go (AppCo co1 co2) = IfaceAppCo (go co1) (go co2) go (SymCo co) = IfaceSymCo (go co) go (TransCo co1 co2) = IfaceTransCo (go co1) (go co2) @@ -236,8 +239,7 @@ toIfaceCoercionX fr co | tc `hasKey` funTyConKey , [_,_,_,_] <- cos = pprPanic "toIfaceCoercion" (ppr co) | otherwise = IfaceTyConAppCo r (toIfaceTyCon tc) (map go cos) - go (FunCo r co1 co2) = IfaceFunCo r (toIfaceCoercion co1) - (toIfaceCoercion co2) + go (FunCo r co1 co2) = IfaceFunCo r (go co1) (go co2) go (ForAllCo tv k co) = IfaceForAllCo (toIfaceTvBndr tv) (toIfaceCoercionX fr' k) diff --git a/testsuite/tests/roles/should_compile/Roles13.stderr b/testsuite/tests/roles/should_compile/Roles13.stderr index f4b44a2..414ef80 100644 --- a/testsuite/tests/roles/should_compile/Roles13.stderr +++ b/testsuite/tests/roles/should_compile/Roles13.stderr @@ -13,7 +13,7 @@ convert :: Wrap Age -> Int [GblId, Arity=1, Caf=NoCafRefs] convert = convert1 - `cast` (_R -> Roles13.N:Wrap[0] Roles13.N:Age[0] + `cast` (_R ->_R Roles13.N:Wrap[0] (Roles13.N:Age[0]) :: (Wrap Age -> Wrap Age :: *) ~R# (Wrap Age -> Int :: *)) -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} From git at git.haskell.org Thu Jul 27 11:49:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 11:49:49 +0000 (UTC) Subject: [commit: ghc] master: Improve error messages around kind mismatches. (8e15e3d) Message-ID: <20170727114949.4E8C83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8e15e3d370e9c253ae0dbb330e25b72cb00cdb76/ghc >--------------------------------------------------------------- commit 8e15e3d370e9c253ae0dbb330e25b72cb00cdb76 Author: Richard Eisenberg Date: Thu Jun 1 17:27:14 2017 -0400 Improve error messages around kind mismatches. Previously, when canonicalizing (or unifying, in uType) a heterogeneous equality, we emitted a kind equality and used the resulting coercion to cast one side of the heterogeneous equality. While sound, this led to terrible error messages. (See the bugs listed below.) The problem is that using the coercion built from the emitted kind equality is a bit like a wanted rewriting a wanted. The solution is to keep heterogeneous equalities as irreducible. See Note [Equalities with incompatible kinds] in TcCanonical. This commit also removes a highly suspicious switch to FM_SubstOnly when flattening in the kinds of a type variable. I have no idea why this was there, other than as a holdover from pre-TypeInType. I've not left a Note because there is simply no reason I can conceive of that the FM_SubstOnly should be there. One challenge with this patch is that the emitted derived equalities might get emitted several times: when a heterogeneous equality is in an implication and then gets floated out from the implication, the Derived is present both in and out of the implication. This causes a duplicate error message. (Test case: typecheck/should_fail/T7368) Solution: track the provenance of Derived constraints and refuse to float out a constraint that has an insoluble Derived. Lastly, this labels one test (dependent/should_fail/RAE_T32a) as expect_broken, because the problem is really #12919. The different handling of constraints in this patch exposes the error. This fixes bugs #11198, #12373, #13530, and #13610. test cases: typecheck/should_fail/{T8262,T8603,tcail122,T12373,T13530,T13610} >--------------------------------------------------------------- 8e15e3d370e9c253ae0dbb330e25b72cb00cdb76 compiler/typecheck/TcCanonical.hs | 296 ++++++++++++--------- compiler/typecheck/TcErrors.hs | 75 ++++-- compiler/typecheck/TcEvidence.hs | 8 +- compiler/typecheck/TcFlatten.hs | 31 ++- compiler/typecheck/TcRnTypes.hs | 30 ++- compiler/typecheck/TcSimplify.hs | 34 ++- compiler/typecheck/TcType.hs | 10 +- compiler/typecheck/TcUnify.hs | 28 +- compiler/types/Type.hs | 4 +- testsuite/tests/dependent/should_fail/T11471.hs | 2 +- .../tests/dependent/should_fail/T11471.stderr | 11 +- testsuite/tests/dependent/should_fail/all.T | 2 +- testsuite/tests/gadt/gadt7.stderr | 6 +- .../tests/ghci.debugger/scripts/break012.stdout | 14 +- .../indexed-types/should_fail/ExtraTcsUntch.stderr | 6 +- .../tests/indexed-types/should_fail/T5934.stderr | 13 - testsuite/tests/polykinds/T12593.stderr | 56 ++++ testsuite/tests/polykinds/T13555.stderr | 21 +- testsuite/tests/polykinds/T7438.stderr | 6 +- testsuite/tests/polykinds/T8566.stderr | 2 +- testsuite/tests/polykinds/T9017.stderr | 10 +- testsuite/tests/typecheck/should_fail/T12373.hs | 10 + .../tests/typecheck/should_fail/T12373.stderr | 8 + testsuite/tests/typecheck/should_fail/T13530.hs | 11 + .../tests/typecheck/should_fail/T13530.stderr | 7 + testsuite/tests/typecheck/should_fail/T13610.hs | 11 + .../tests/typecheck/should_fail/T13610.stderr | 14 + testsuite/tests/typecheck/should_fail/T5691.stderr | 10 +- testsuite/tests/typecheck/should_fail/T7368.stderr | 6 +- .../tests/typecheck/should_fail/T7368a.stderr | 2 +- testsuite/tests/typecheck/should_fail/T7453.stderr | 48 +--- testsuite/tests/typecheck/should_fail/T7696.stderr | 4 +- testsuite/tests/typecheck/should_fail/T8262.stderr | 6 +- testsuite/tests/typecheck/should_fail/T8603.hs | 4 + testsuite/tests/typecheck/should_fail/T8603.stderr | 13 +- testsuite/tests/typecheck/should_fail/all.T | 3 + .../tests/typecheck/should_fail/tcfail090.stderr | 4 +- .../tests/typecheck/should_fail/tcfail122.stderr | 8 +- .../tests/typecheck/should_fail/tcfail123.stderr | 13 +- .../tests/typecheck/should_fail/tcfail200.stderr | 6 +- 40 files changed, 537 insertions(+), 316 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 8e15e3d370e9c253ae0dbb330e25b72cb00cdb76 From git at git.haskell.org Thu Jul 27 11:49:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 11:49:52 +0000 (UTC) Subject: [commit: ghc] master: Test #11672 in typecheck/should_fail/T11672. (9a54975) Message-ID: <20170727114952.E024D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9a54975665f23df8c8137da24028a5aec4c77fba/ghc >--------------------------------------------------------------- commit 9a54975665f23df8c8137da24028a5aec4c77fba Author: Richard Eisenberg Date: Thu Jun 1 18:28:57 2017 -0400 Test #11672 in typecheck/should_fail/T11672. I believe this was fixed with the fix for #11198. >--------------------------------------------------------------- 9a54975665f23df8c8137da24028a5aec4c77fba testsuite/tests/typecheck/should_fail/T11672.hs | 9 +++++++++ testsuite/tests/typecheck/should_fail/T11672.stderr | 21 +++++++++++++++++++++ testsuite/tests/typecheck/should_fail/all.T | 2 ++ 3 files changed, 32 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T11672.hs b/testsuite/tests/typecheck/should_fail/T11672.hs new file mode 100644 index 0000000..8c5e2fb --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T11672.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE KindSignatures #-} +module BadError where + +import GHC.TypeLits +import Data.Proxy + +f :: Proxy (a :: Symbol) -> Int +f _ = f (Proxy :: Proxy (Int -> Bool)) diff --git a/testsuite/tests/typecheck/should_fail/T11672.stderr b/testsuite/tests/typecheck/should_fail/T11672.stderr new file mode 100644 index 0000000..d08acba --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T11672.stderr @@ -0,0 +1,21 @@ + +T11672.hs:9:10: error: + • Couldn't match kind ‘Symbol’ with ‘*’ + When matching types + a0 :: Symbol + Int -> Bool :: * + Expected type: Proxy a0 + Actual type: Proxy (Int -> Bool) + • In the first argument of ‘f’, namely + ‘(Proxy :: Proxy (Int -> Bool))’ + In the expression: f (Proxy :: Proxy (Int -> Bool)) + In an equation for ‘f’: f _ = f (Proxy :: Proxy (Int -> Bool)) + +T11672.hs:9:10: error: + • Couldn't match type ‘*’ with ‘Symbol’ + Expected type: Proxy a0 + Actual type: Proxy (Int -> Bool) + • In the first argument of ‘f’, namely + ‘(Proxy :: Proxy (Int -> Bool))’ + In the expression: f (Proxy :: Proxy (Int -> Bool)) + In an equation for ‘f’: f _ = f (Proxy :: Proxy (Int -> Bool)) diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 06789ed..4a1d748 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -449,3 +449,5 @@ test('T13983', normal, compile_fail, ['']) test('T13530', normal, compile_fail, ['']) test('T12373', normal, compile_fail, ['']) test('T13610', normal, compile_fail, ['']) +test('T11672', normal, compile_fail, ['']) + From git at git.haskell.org Thu Jul 27 11:49:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 11:49:55 +0000 (UTC) Subject: [commit: ghc] master: Fix #11400, #11560 by documenting an infelicity. (c9667d3) Message-ID: <20170727114955.9E5D13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c9667d321c94ff0f67b73aa7bd560c38873f7df5/ghc >--------------------------------------------------------------- commit c9667d321c94ff0f67b73aa7bd560c38873f7df5 Author: Richard Eisenberg Date: Thu Jun 1 18:09:05 2017 -0400 Fix #11400, #11560 by documenting an infelicity. Really, the fix for both of these is #11307. >--------------------------------------------------------------- c9667d321c94ff0f67b73aa7bd560c38873f7df5 docs/users_guide/glasgow_exts.rst | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index a2cc0ba..7fc075a 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -8347,9 +8347,9 @@ enabled). The only way ``*`` is unordinary is in its parsing. In order to be backward compatible, ``*`` is parsed as if it were an alphanumeric idenfifier; note that we do not write ``Int :: (*)`` but just plain ``Int :: *``. Due to the -bizarreness with which ``*`` is parsed-and the fact that it is the only such -operator in GHC-there are some corner cases that are -not handled. We are aware of two: +bizarreness with which ``*`` is parsed--and the fact that it is the only such +operator in GHC--there are some corner cases that are +not handled. We are aware of three: - In a Haskell-98-style data constructor, you must put parentheses around ``*``, like this: :: @@ -8363,6 +8363,10 @@ not handled. We are aware of two: Note that the keyword ``type`` there is just to disambiguate the import from a term-level ``(*)``. (:ref:`explicit-namespaces`) +- In an instance declaration head (the part after the word ``instance``), you + must parenthesize ``*``. This applies to all manners of instances, including + the left-hand sides of individual equations of a closed type family. + The ``Data.Kind`` module also exports ``Type`` as a synonym for ``*``. Now that type synonyms work in kinds, it is conceivable that we will deprecate ``*`` when there is a good migration story for everyone to use ``Type``. From git at git.haskell.org Thu Jul 27 11:49:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 11:49:58 +0000 (UTC) Subject: [commit: ghc] master: Track visibility in TypeEqOrigin (fb75213) Message-ID: <20170727114958.6B52C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fb752133f45f01b27240d7cc6bce2063a015e51b/ghc >--------------------------------------------------------------- commit fb752133f45f01b27240d7cc6bce2063a015e51b Author: Richard Eisenberg Date: Tue Jul 18 14:30:40 2017 -0400 Track visibility in TypeEqOrigin A type equality error can arise from a mismatch between *invisible* arguments just as easily as from visible arguments. But we should really prefer printing out errors from visible arguments over invisible ones. Suppose we have a mismatch between `Proxy Int` and `Proxy Maybe`. Would you rather get an error between `Int` and `Maybe`? Or between `*` and `* -> *`? I thought so, too. There is a fair amount of plumbing with this one, but I think it's worth it. This commit introduces a performance regression in test perf/compiler/T5631. The cause of the regression is not the new visibility stuff, directly: it's due to a change from zipWithM to zipWith3M in TcUnify. To my surprise, zipWithM is nicely optimized (it fuses away), but zipWith3M is not. There are other examples of functions that could be made faster, so I've posted a separate ticket, #14037, to track these improvements. For now, I've accepted the small (6.6%) regression. >--------------------------------------------------------------- fb752133f45f01b27240d7cc6bce2063a015e51b compiler/typecheck/Inst.hs | 3 +- compiler/typecheck/TcCanonical.hs | 18 +++-- compiler/typecheck/TcErrors.hs | 29 ++++---- compiler/typecheck/TcHsType.hs | 5 +- compiler/typecheck/TcRnTypes.hs | 30 ++++++++- compiler/typecheck/TcType.hs | 38 ++++++++++- compiler/typecheck/TcUnify.hs | 78 +++++++++++++--------- testsuite/tests/perf/compiler/all.T | 4 +- testsuite/tests/polykinds/KindVType.stderr | 2 +- .../tests/typecheck/should_fail/T12373.stderr | 3 + .../tests/typecheck/should_fail/T13530.stderr | 3 + testsuite/tests/typecheck/should_fail/T8603.stderr | 7 +- 12 files changed, 153 insertions(+), 67 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 fb752133f45f01b27240d7cc6bce2063a015e51b From git at git.haskell.org Thu Jul 27 11:50:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 11:50:01 +0000 (UTC) Subject: [commit: ghc] master: Refactor tcInferApps. (791947d) Message-ID: <20170727115001.3D03D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/791947db6db32ef7d4772a821a0823e558e3c05b/ghc >--------------------------------------------------------------- commit 791947db6db32ef7d4772a821a0823e558e3c05b Author: Richard Eisenberg Date: Mon Jul 24 15:49:00 2017 -0400 Refactor tcInferApps. With the changes caused by the fix to #12369, it is now clearer how to rewrite tcInferApps and friends. This should change no behavior, but it does clean up a nasty corner of the type checker. This commit also removes some uses of substTyUnchecked. >--------------------------------------------------------------- 791947db6db32ef7d4772a821a0823e558e3c05b compiler/typecheck/TcHsType.hs | 115 +++++++++++++++++++++-------------------- compiler/types/TyCoRep.hs | 10 ++-- compiler/types/Type.hs | 2 +- 3 files changed, 64 insertions(+), 63 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 791947db6db32ef7d4772a821a0823e558e3c05b From git at git.haskell.org Thu Jul 27 11:50:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 11:50:03 +0000 (UTC) Subject: [commit: ghc] master: Document that type holes kill polymorphic recursion (ca47186) Message-ID: <20170727115003.F17A73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ca471860494484210b6291dd96d1e0868da750e7/ghc >--------------------------------------------------------------- commit ca471860494484210b6291dd96d1e0868da750e7 Author: Richard Eisenberg Date: Tue Jul 18 15:55:21 2017 -0400 Document that type holes kill polymorphic recursion This "fixes" #11995. >--------------------------------------------------------------- ca471860494484210b6291dd96d1e0868da750e7 docs/users_guide/glasgow_exts.rst | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 7fc075a..b0da2891 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -10290,6 +10290,10 @@ warnings instead of errors. Additionally, these warnings can be silenced with the :ghc-flag:`-Wno-partial-type-signatures <-Wpartial-type-signatures>` flag. +However, because GHC must *infer* the type when part of a type is left +out, it is unable to use polymorphic recursion. The same restriction +takes place when the type signature is omitted completely. + .. _pts-syntax: Syntax From git at git.haskell.org Thu Jul 27 11:50:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 11:50:06 +0000 (UTC) Subject: [commit: ghc] master: Remove old coercion pretty-printer (79cfb19) Message-ID: <20170727115006.BA74F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/79cfb1999474ad15dd955a10c846c8ea87e612c2/ghc >--------------------------------------------------------------- commit 79cfb1999474ad15dd955a10c846c8ea87e612c2 Author: Richard Eisenberg Date: Tue Jun 6 11:01:14 2017 -0400 Remove old coercion pretty-printer Now, all coercions are printed from IfaceType, just like types. This also changes the rendering of TransCo to use ; instead of a prefix operator. >--------------------------------------------------------------- 79cfb1999474ad15dd955a10c846c8ea87e612c2 compiler/iface/IfaceType.hs | 3 +- compiler/iface/ToIface.hs | 4 +- compiler/iface/ToIface.hs-boot | 2 +- compiler/types/Coercion.hs | 107 +++++----------------------------------- compiler/types/Coercion.hs-boot | 3 -- compiler/types/TyCoRep.hs | 35 ++++++++++--- compiler/types/Type.hs | 2 +- compiler/types/Type.hs-boot | 7 +-- 8 files changed, 49 insertions(+), 114 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 79cfb1999474ad15dd955a10c846c8ea87e612c2 From git at git.haskell.org Thu Jul 27 11:50:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 11:50:10 +0000 (UTC) Subject: [commit: ghc] master: Fix #12369 by being more flexible with data insts (4239238) Message-ID: <20170727115010.1306E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4239238306e911803bf61fdda3ad356fd0b42e05/ghc >--------------------------------------------------------------- commit 4239238306e911803bf61fdda3ad356fd0b42e05 Author: Richard Eisenberg Date: Wed Jul 19 12:28:04 2017 -0400 Fix #12369 by being more flexible with data insts Previously, a data family's kind had to end in `Type`, and data instances had to list all the type patterns for the family. However, both of these restrictions were unnecessary: - A data family's kind can usefully end in a kind variable `k`. See examples on #12369. - A data instance need not list all patterns, much like how a GADT-style data declaration need not list all type parameters, when a kind signature is in place. This is useful, for example, here: data family Sing (a :: k) data instance Sing :: Bool -> Type where ... This patch also improved a few error messages, as some error plumbing had to be moved around. See new Note [Arity of data families] in FamInstEnv for more info. test case: indexed-types/should_compile/T12369 >--------------------------------------------------------------- 4239238306e911803bf61fdda3ad356fd0b42e05 compiler/typecheck/TcHsSyn.hs | 2 +- compiler/typecheck/TcHsType.hs | 175 ++++++++------- compiler/typecheck/TcInstDcls.hs | 25 ++- compiler/typecheck/TcTyClsDecls.hs | 239 ++++++++++++++++----- compiler/typecheck/TcValidity.hs | 42 ++-- compiler/types/FamInstEnv.hs | 43 +++- compiler/types/TyCon.hs | 10 +- compiler/types/Type.hs | 2 +- docs/users_guide/8.4.1-notes.rst | 6 + docs/users_guide/glasgow_exts.rst | 5 + .../tests/indexed-types/should_compile/T12369.hs | 35 +++ testsuite/tests/indexed-types/should_compile/all.T | 1 + .../indexed-types/should_fail/ExtraTcsUntch.stderr | 6 +- .../indexed-types/should_fail/Overlap4.stderr | 8 +- .../indexed-types/should_fail/SimpleFail1b.stderr | 8 +- .../indexed-types/should_fail/TyFamArity1.stderr | 8 +- .../indexed-types/should_fail/TyFamArity2.stderr | 9 +- 17 files changed, 415 insertions(+), 209 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 4239238306e911803bf61fdda3ad356fd0b42e05 From git at git.haskell.org Thu Jul 27 11:50:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 11:50:13 +0000 (UTC) Subject: [commit: ghc] master: Fix #11963 by checking for more mixed type/kinds (10d13b6) Message-ID: <20170727115013.5FD333A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/10d13b62c7ba8c44000a0d25afd66788de8040c4/ghc >--------------------------------------------------------------- commit 10d13b62c7ba8c44000a0d25afd66788de8040c4 Author: Richard Eisenberg Date: Tue Jul 18 15:49:38 2017 -0400 Fix #11963 by checking for more mixed type/kinds This is a straightforward fix -- there were just some omitted checks. test case: typecheck/should_fail/T11963 >--------------------------------------------------------------- 10d13b62c7ba8c44000a0d25afd66788de8040c4 compiler/rename/RnTypes.hs | 25 +++++++++++++++---- testsuite/tests/typecheck/should_fail/T11963.hs | 29 ++++++++++++++++++++++ .../tests/typecheck/should_fail/T11963.stderr | 20 +++++++++++++++ testsuite/tests/typecheck/should_fail/all.T | 2 +- 4 files changed, 70 insertions(+), 6 deletions(-) diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs index 014d485..a0ceb32 100644 --- a/compiler/rename/RnTypes.hs +++ b/compiler/rename/RnTypes.hs @@ -1717,11 +1717,25 @@ extract_hs_tv_bndrs tvs = do { FKTV bndr_kvs _ <- foldrM extract_lkind emptyFKTV [k | L _ (KindedTyVar _ k) <- tvs] - ; let locals = map hsLTyVarName tvs + ; let locals = map hsLTyVarLocName tvs + + -- These checks are all tested in typecheck/should_fail/T11963 + ; check_for_mixed_vars bndr_kvs acc_tvs + ; check_for_mixed_vars bndr_kvs body_tvs + ; check_for_mixed_vars body_tvs acc_kvs + ; check_for_mixed_vars body_kvs acc_tvs + ; check_for_mixed_vars locals body_kvs + ; return $ - FKTV (filterOut ((`elem` locals) . unLoc) (bndr_kvs ++ body_kvs) + FKTV (filterOut (`elemRdr` locals) (bndr_kvs ++ body_kvs) ++ acc_kvs) - (filterOut ((`elem` locals) . unLoc) body_tvs ++ acc_tvs) } + (filterOut (`elemRdr` locals) body_tvs ++ acc_tvs) } + where + check_for_mixed_vars :: [Located RdrName] -> [Located RdrName] -> RnM () + check_for_mixed_vars tvs1 tvs2 = mapM_ check tvs1 + where + check tv1 = when (isRdrTyVar (unLoc tv1) && (tv1 `elemRdr` tvs2)) $ + mixedVarsErr tv1 extract_tv :: TypeOrKind -> Located RdrName -> FreeKiTyVars -> RnM FreeKiTyVars @@ -1737,8 +1751,6 @@ extract_tv t_or_k ltv@(L _ tv) acc mixedVarsErr ltv ; return (FKTV (ltv : kvs) tvs) } | otherwise = return acc - where - elemRdr x = any (eqLocated x) mixedVarsErr :: Located RdrName -> RnM () mixedVarsErr (L loc tv) @@ -1751,3 +1763,6 @@ mixedVarsErr (L loc tv) -- just used in this module; seemed convenient here nubL :: Eq a => [Located a] -> [Located a] nubL = nubBy eqLocated + +elemRdr :: Located RdrName -> [Located RdrName] -> Bool +elemRdr x = any (eqLocated x) diff --git a/testsuite/tests/typecheck/should_fail/T11963.hs b/testsuite/tests/typecheck/should_fail/T11963.hs new file mode 100644 index 0000000..c4f78ae --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T11963.hs @@ -0,0 +1,29 @@ +{-# LANGUAGE GADTs, PolyKinds, RankNTypes #-} + +module T11963 where + +-- this module should be rejected without TypeInType + +import Data.Proxy + +-- see code in RnTypes.extract_hs_tv_bndrs which checks for these bad cases + + -- bndr_kvs vs body_tvs +data Typ k t where + Typ :: (forall (a :: k -> *). a t -> a t) -> Typ k t + + -- bndr_kvs vs acc_tvs +foo :: (forall (t :: k). Proxy t) -> Proxy k +foo _ = undefined + + -- locals vs body_kvs +bar :: forall k. forall (t :: k). Proxy t +bar = undefined + + -- body_kvs vs acc_tvs +quux :: (forall t. Proxy (t :: k)) -> Proxy k +quux _ = undefined + + -- body_tvs vs acc_kvs +blargh :: (forall a. a -> Proxy k) -> Proxy (t :: k) +blargh _ = undefined diff --git a/testsuite/tests/typecheck/should_fail/T11963.stderr b/testsuite/tests/typecheck/should_fail/T11963.stderr new file mode 100644 index 0000000..74c3ab0 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T11963.stderr @@ -0,0 +1,20 @@ + +T11963.hs:13:26: error: + Variable ‘k’ used as both a kind and a type + Did you intend to use TypeInType? + +T11963.hs:16:22: error: + Variable ‘k’ used as both a kind and a type + Did you intend to use TypeInType? + +T11963.hs:20:15: error: + Variable ‘k’ used as both a kind and a type + Did you intend to use TypeInType? + +T11963.hs:24:32: error: + Variable ‘k’ used as both a kind and a type + Did you intend to use TypeInType? + +T11963.hs:28:33: error: + Variable ‘k’ used as both a kind and a type + Did you intend to use TypeInType? diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 58ae57f..3d2a595 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -451,4 +451,4 @@ test('T12373', normal, compile_fail, ['']) test('T13610', normal, compile_fail, ['']) test('T11672', normal, compile_fail, ['']) test('T13819', normal, compile_fail, ['']) - +test('T11963', normal, compile_fail, ['']) From git at git.haskell.org Thu Jul 27 11:50:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 11:50:16 +0000 (UTC) Subject: [commit: ghc] master: Fix #12176 by being a bit more careful instantiating. (1696dbf) Message-ID: <20170727115016.9F24C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1696dbf4ad0fda4d7c5b4afe1911cab51d7dd0b0/ghc >--------------------------------------------------------------- commit 1696dbf4ad0fda4d7c5b4afe1911cab51d7dd0b0 Author: Richard Eisenberg Date: Tue Jul 18 19:44:17 2017 -0400 Fix #12176 by being a bit more careful instantiating. Previously, looking up a TyCon that said "no" to mightBeUnsaturated would then instantiate all of its invisible binders. But this is wrong for vanilla type synonyms, whose RHS kind might legitimately start with invisible binders. So a little more care is taken now, only to instantiate those invisible binders that need to be (so that the TyCon isn't unsaturated). >--------------------------------------------------------------- 1696dbf4ad0fda4d7c5b4afe1911cab51d7dd0b0 compiler/typecheck/TcCanonical.hs | 4 +- compiler/typecheck/TcHsType.hs | 50 ++++++++++++++-------- testsuite/tests/dependent/should_compile/T12176.hs | 18 ++++++++ testsuite/tests/dependent/should_compile/all.T | 1 + 4 files changed, 53 insertions(+), 20 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 23de0e5..48c1bec 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -24,7 +24,7 @@ import FamInstEnv ( FamInstEnvs ) import FamInst ( tcTopNormaliseNewTypeTF_maybe ) import Var import VarEnv( mkInScopeSet ) -import VarSet( extendVarSetList ) +import VarSet import Outputable import DynFlags( DynFlags ) import NameSet @@ -683,7 +683,7 @@ can_eq_nc_forall ev eq_rel s1 s2 go _ _ _ = panic "cna_eq_nc_forall" -- case (s:ss) [] empty_subst2 = mkEmptyTCvSubst $ mkInScopeSet $ - free_tvs2 `extendVarSetList` skol_tvs + free_tvs2 `unionVarSet` closeOverKinds (mkVarSet skol_tvs) ; (implic, _ev_binds, all_co) <- buildImplication skol_info skol_tvs [] $ go skol_tvs empty_subst2 bndrs2 diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 185c034..01c9adb 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -922,30 +922,42 @@ checkExpectedKind hs_ty ty act_kind exp_kind , TcKind ) -- its new kind instantiate ty act_ki exp_ki = let (exp_bndrs, _) = splitPiTysInvisible exp_ki in - instantiateTyN (length exp_bndrs) ty act_ki - --- | Instantiate a type to have at most @n@ invisible arguments. -instantiateTyN :: Int -- ^ @n@ - -> TcType -- ^ the type - -> TcKind -- ^ its kind - -> TcM (TcType, TcKind) -- ^ The inst'ed type with kind -instantiateTyN n ty ki - = let (bndrs, inner_ki) = splitPiTysInvisible ki - num_to_inst = length bndrs - n - -- NB: splitAt is forgiving with invalid numbers - (inst_bndrs, leftover_bndrs) = splitAt num_to_inst bndrs + instantiateTyUntilN (length exp_bndrs) ty act_ki + +-- | Instantiate @n@ invisible arguments to a type. If @n <= 0@, no instantiation +-- occurs. If @n@ is too big, then all available invisible arguments are instantiated. +-- (In other words, this function is very forgiving about bad values of @n at .) +instantiateTyN :: Int -- ^ @n@ + -> TcType -- ^ the type + -> [TyBinder] -> TcKind -- ^ its kind + -> TcM (TcType, TcKind) -- ^ The inst'ed type with kind +instantiateTyN n ty bndrs inner_ki + = let -- NB: splitAt is forgiving with invalid numbers + (inst_bndrs, leftover_bndrs) = splitAt n bndrs + ki = mkPiTys bndrs inner_ki empty_subst = mkEmptyTCvSubst (mkInScopeSet (tyCoVarsOfType ki)) in - if num_to_inst <= 0 then return (ty, ki) else + if n <= 0 then return (ty, ki) else do { (subst, inst_args) <- tcInstBinders empty_subst Nothing inst_bndrs ; let rebuilt_ki = mkPiTys leftover_bndrs inner_ki ki' = substTy subst rebuilt_ki ; traceTc "instantiateTyN" (vcat [ ppr ty <+> dcolon <+> ppr ki + , ppr n , ppr subst , ppr rebuilt_ki , ppr ki' ]) ; return (mkNakedAppTys ty inst_args, ki') } +-- | Instantiate a type to have at most @n@ invisible arguments. +instantiateTyUntilN :: Int -- ^ @n@ + -> TcType -- ^ the type + -> TcKind -- ^ its kind + -> TcM (TcType, TcKind) -- ^ The inst'ed type with kind +instantiateTyUntilN n ty ki + = let (bndrs, inner_ki) = splitPiTysInvisible ki + num_to_inst = length bndrs - n + in + instantiateTyN num_to_inst ty bndrs inner_ki --------------------------- tcHsContext :: LHsContext GhcRn -> TcM [PredType] @@ -1018,8 +1030,8 @@ tcTyVar mode name -- Could be a tyvar, a tycon, or a datacon -- if we are type-checking a type family tycon, we must instantiate -- any invisible arguments right away. Otherwise, we get #11246 - handle_tyfams :: TyCon -- the tycon to instantiate (might be loopy) - -> TyCon -- a non-loopy version of the tycon + handle_tyfams :: TyCon -- the tycon to instantiate (might be loopy) + -> TcTyCon -- a non-loopy version of the tycon -> TcM (TcType, TcKind) handle_tyfams tc tc_tc | mightBeUnsaturatedTyCon tc_tc @@ -1027,7 +1039,8 @@ tcTyVar mode name -- Could be a tyvar, a tycon, or a datacon ; return (ty, tc_kind) } | otherwise - = do { (tc_ty, kind) <- instantiateTyN 0 ty tc_kind + = do { (tc_ty, kind) <- instantiateTyN (length (tyConBinders tc_tc)) + ty tc_kind_bndrs tc_inner_ki -- tc and tc_ty must not be traced here, because that would -- force the evaluation of a potentially knot-tied variable (tc), -- and the typechecker would hang, as per #11708 @@ -1035,8 +1048,9 @@ tcTyVar mode name -- Could be a tyvar, a tycon, or a datacon , ppr kind ]) ; return (tc_ty, kind) } where - ty = mkNakedTyConApp tc [] - tc_kind = tyConKind tc_tc + ty = mkNakedTyConApp tc [] + tc_kind = tyConKind tc_tc + (tc_kind_bndrs, tc_inner_ki) = splitPiTysInvisible tc_kind get_loopy_tc :: Name -> TyCon -> TcM TyCon -- Return the knot-tied global TyCon if there is one diff --git a/testsuite/tests/dependent/should_compile/T12176.hs b/testsuite/tests/dependent/should_compile/T12176.hs new file mode 100644 index 0000000..0e34006 --- /dev/null +++ b/testsuite/tests/dependent/should_compile/T12176.hs @@ -0,0 +1,18 @@ +{-# LANGUAGE RankNTypes, TypeInType, GADTs, TypeFamilies #-} + +module T12176 where + +import Data.Kind + +data Proxy :: forall k. k -> Type where + MkProxy :: forall k (a :: k). Proxy a + +data X where + MkX :: forall (k :: Type) (a :: k). Proxy a -> X + +type Expr = (MkX :: forall (a :: Bool). Proxy a -> X) + +type family Foo (x :: forall (a :: k). Proxy a -> X) where + Foo (MkX :: forall (a :: k). Proxy a -> X) = (MkProxy :: Proxy k) + +type Bug = Foo Expr -- this failed with #12176 diff --git a/testsuite/tests/dependent/should_compile/all.T b/testsuite/tests/dependent/should_compile/all.T index 8a9b221..b854f1d 100644 --- a/testsuite/tests/dependent/should_compile/all.T +++ b/testsuite/tests/dependent/should_compile/all.T @@ -24,3 +24,4 @@ test('T11719', normal, compile, ['']) test('T11966', normal, compile, ['']) test('T12442', normal, compile, ['']) test('T13538', normal, compile, ['']) +test('T12176', normal, compile, ['']) From git at git.haskell.org Thu Jul 27 11:50:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 11:50:20 +0000 (UTC) Subject: [commit: ghc] master: Fix #13819 by refactoring TypeEqOrigin.uo_thing (c2417b8) Message-ID: <20170727115020.919C33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c2417b87ff59c92fbfa8eceeff2a0d6152b11a47/ghc >--------------------------------------------------------------- commit c2417b87ff59c92fbfa8eceeff2a0d6152b11a47 Author: Richard Eisenberg Date: Wed Jun 14 16:35:18 2017 -0400 Fix #13819 by refactoring TypeEqOrigin.uo_thing The uo_thing field of TypeEqOrigin is used to track the "thing" (either term or type) that has the type (kind) stored in the TypeEqOrigin fields. Previously, this was sometimes a proper Core Type, which needed zonking and tidying. Now, it is only HsSyn: much simpler, and the error messages now use the user-written syntax. But this aspect of uo_thing didn't cause #13819; it was the sibling field uo_arity that did. uo_arity stored the number of arguments of uo_thing, useful when reporting something like "should have written 2 fewer arguments". We wouldn't want to say that if the thing didn't have two arguments. However, in practice, GHC was getting this wrong, and this message didn't seem all that helpful. Furthermore, the calculation of the number of arguments is what caused #13819 to fall over. This patch just removes uo_arity. In my opinion, the change to error messages is a nudge in the right direction. Test case: typecheck/should_fail/T13819 >--------------------------------------------------------------- c2417b87ff59c92fbfa8eceeff2a0d6152b11a47 compiler/ghci/RtClosureInspect.hs | 4 +- compiler/typecheck/Inst.hs | 8 +- compiler/typecheck/TcArrows.hs | 2 +- compiler/typecheck/TcErrors.hs | 20 ++- compiler/typecheck/TcExpr.hs | 50 ++++---- compiler/typecheck/TcHsType.hs | 135 +++++++++++---------- compiler/typecheck/TcMType.hs | 30 +---- compiler/typecheck/TcPat.hs | 6 +- compiler/typecheck/TcRnTypes.hs | 21 +--- compiler/typecheck/TcSigs.hs | 4 +- compiler/typecheck/TcSplice.hs | 13 +- compiler/typecheck/TcSplice.hs-boot | 6 +- compiler/typecheck/TcTyClsDecls.hs | 2 +- compiler/typecheck/TcType.hs | 7 ++ compiler/typecheck/TcUnify.hs | 65 +++++----- compiler/typecheck/TcUnify.hs-boot | 7 +- compiler/types/Type.hs | 2 +- .../tests/indexed-types/should_fail/T12867.stderr | 3 +- testsuite/tests/polykinds/T12593.stderr | 7 +- testsuite/tests/polykinds/T6039.stderr | 3 +- testsuite/tests/polykinds/T7278.stderr | 3 +- testsuite/tests/polykinds/T8616.stderr | 2 +- testsuite/tests/polykinds/T9200b.stderr | 6 +- .../tests/rename/should_fail/rnfail026.stderr | 3 +- testsuite/tests/th/T3177a.stderr | 6 +- .../tests/typecheck/should_fail/T11356.stderr | 3 +- .../tests/typecheck/should_fail/T11672.stderr | 11 +- .../tests/typecheck/should_fail/T12785b.stderr | 6 + testsuite/tests/typecheck/should_fail/T13819.hs | 14 +++ .../tests/typecheck/should_fail/T13819.stderr | 18 +++ testsuite/tests/typecheck/should_fail/T2994.stderr | 3 +- testsuite/tests/typecheck/should_fail/T3540.stderr | 2 +- testsuite/tests/typecheck/should_fail/T4875.stderr | 6 +- testsuite/tests/typecheck/should_fail/T7609.stderr | 11 +- testsuite/tests/typecheck/should_fail/T7778.stderr | 10 +- testsuite/tests/typecheck/should_fail/all.T | 1 + .../tests/typecheck/should_fail/tcfail070.stderr | 3 +- .../tests/typecheck/should_fail/tcfail078.stderr | 6 +- .../tests/typecheck/should_fail/tcfail113.stderr | 12 +- .../tests/typecheck/should_fail/tcfail123.stderr | 9 -- .../tests/typecheck/should_fail/tcfail132.stderr | 3 +- 41 files changed, 243 insertions(+), 290 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 c2417b87ff59c92fbfa8eceeff2a0d6152b11a47 From git at git.haskell.org Thu Jul 27 20:18:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:18:33 +0000 (UTC) Subject: [commit: ghc] master: Initialize hs_init with UTF8 encoded arguments on Windows. (7af0b90) Message-ID: <20170727201833.D44CB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7af0b906116e13fbd90f43f2f6c6b826df2dca77/ghc >--------------------------------------------------------------- commit 7af0b906116e13fbd90f43f2f6c6b826df2dca77 Author: Andreas Klebinger Date: Thu Jul 27 18:16:09 2017 +0100 Initialize hs_init with UTF8 encoded arguments on Windows. Summary: Get utf8 encoded arguments before we call hs_init and use them instead of ignoring hs_init arguments. This reduces differing behaviour of the RTS between windows and linux and simplifies the code involved. A few testcases were changed to expect the same result on windows as on linux after the changes. This fixes #13940. Test Plan: ./validate Reviewers: austin, hvr, bgamari, erikd, simonmar, Phyx Subscribers: Phyx, rwbarton, thomie GHC Trac Issues: #13940 Differential Revision: https://phabricator.haskell.org/D3739 >--------------------------------------------------------------- 7af0b906116e13fbd90f43f2f6c6b826df2dca77 docs/users_guide/ffi-chap.rst | 6 ++ includes/Rts.h | 6 -- libraries/base/GHC/Environment.hs | 45 ++-------- libraries/base/GHC/IO/Encoding.hs | 12 +++ libraries/base/System/Environment.hs | 92 ++------------------ rts/RtsFlags.c | 127 +++++++++++++++++----------- rts/RtsFlags.h | 5 ++ rts/RtsMain.c | 11 +++ rts/RtsStartup.c | 26 ++++++ rts/RtsSymbols.c | 2 - testsuite/tests/ghci.debugger/scripts/all.T | 3 +- testsuite/tests/rts/T6006.stdout-mingw32 | 2 +- 12 files changed, 155 insertions(+), 182 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 7af0b906116e13fbd90f43f2f6c6b826df2dca77 From git at git.haskell.org Thu Jul 27 20:48:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:09 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (4b1e8ac) Message-ID: <20170727204809.0DDF43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/4b1e8ac884480df3ad20dc6eeb5857f12c552d81/ghc >--------------------------------------------------------------- commit 4b1e8ac884480df3ad20dc6eeb5857f12c552d81 Author: Ben Gamari Date: Thu May 18 02:56:06 2017 -0400 Debug >--------------------------------------------------------------- 4b1e8ac884480df3ad20dc6eeb5857f12c552d81 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 Jul 27 20:48:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:14 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Disable large address space on FreeBSD (7d88f01) Message-ID: <20170727204814.8B6673A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7d88f01ad2c3d2a5d8f90e6ed8e48eeac643e63c/ghc >--------------------------------------------------------------- commit 7d88f01ad2c3d2a5d8f90e6ed8e48eeac643e63c Author: Ben Gamari Date: Mon May 29 16:34:26 2017 -0400 Disable large address space on FreeBSD >--------------------------------------------------------------- 7d88f01ad2c3d2a5d8f90e6ed8e48eeac643e63c 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 Thu Jul 27 20:48:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:11 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add nofib, bindist, and aarch64 support (a3b22d6) Message-ID: <20170727204811.CB64E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a3b22d644808f800667a72eb4c76e4d0817a6bbb/ghc >--------------------------------------------------------------- commit a3b22d644808f800667a72eb4c76e4d0817a6bbb Author: Ben Gamari Date: Wed May 17 22:41:02 2017 -0400 Add nofib, bindist, and aarch64 support >--------------------------------------------------------------- a3b22d644808f800667a72eb4c76e4d0817a6bbb 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 Jul 27 20:48:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:17 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Unregisterised (9d6d2b3) Message-ID: <20170727204817.481883A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9d6d2b3b408d0a3b2ac8dbdb47cd1968e1a956a6/ghc >--------------------------------------------------------------- commit 9d6d2b3b408d0a3b2ac8dbdb47cd1968e1a956a6 Author: Ben Gamari Date: Thu May 18 01:55:35 2017 -0400 Unregisterised >--------------------------------------------------------------- 9d6d2b3b408d0a3b2ac8dbdb47cd1968e1a956a6 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 Jul 27 20:48:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:20 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix FreeBSD architecture (5e7868b) Message-ID: <20170727204820.0619A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/5e7868b81b4f8743096d336f331e856bb239e118/ghc >--------------------------------------------------------------- commit 5e7868b81b4f8743096d336f331e856bb239e118 Author: Ben Gamari Date: Mon May 29 13:55:03 2017 -0400 Fix FreeBSD architecture >--------------------------------------------------------------- 5e7868b81b4f8743096d336f331e856bb239e118 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 Thu Jul 27 20:48:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:22 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Hmm (c8b1b62) Message-ID: <20170727204822.AFF413A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c8b1b620f9f406d2a8eb09eafc0a9b09b85b7f74/ghc >--------------------------------------------------------------- commit c8b1b620f9f406d2a8eb09eafc0a9b09b85b7f74 Author: Ben Gamari Date: Mon May 29 16:45:16 2017 -0400 Hmm >--------------------------------------------------------------- c8b1b620f9f406d2a8eb09eafc0a9b09b85b7f74 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 Thu Jul 27 20:48:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:25 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring (f777704) Message-ID: <20170727204825.6B36A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/f77770466c4cee8be0a6e75ea43a69df2de6fd90/ghc >--------------------------------------------------------------- commit f77770466c4cee8be0a6e75ea43a69df2de6fd90 Author: Ben Gamari Date: Wed May 17 20:20:55 2017 -0400 Refactoring >--------------------------------------------------------------- f77770466c4cee8be0a6e75ea43a69df2de6fd90 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 Jul 27 20:48:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:28 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Kill debugging (9b24deb) Message-ID: <20170727204828.2587B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9b24deb90ce9a731a4fbb668ed73116de1edcfe5/ghc >--------------------------------------------------------------- commit 9b24deb90ce9a731a4fbb668ed73116de1edcfe5 Author: Ben Gamari Date: Thu May 18 01:39:32 2017 -0400 Kill debugging >--------------------------------------------------------------- 9b24deb90ce9a731a4fbb668ed73116de1edcfe5 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 Jul 27 20:48:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:36 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Try again (1f755f4) Message-ID: <20170727204836.4A5893A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/1f755f4f59d8c9d73d50a0276e10124f31dd2797/ghc >--------------------------------------------------------------- commit 1f755f4f59d8c9d73d50a0276e10124f31dd2797 Author: Ben Gamari Date: Mon May 29 16:42:42 2017 -0400 Try again >--------------------------------------------------------------- 1f755f4f59d8c9d73d50a0276e10124f31dd2797 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 Thu Jul 27 20:48:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:33 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (69b9ddd) Message-ID: <20170727204833.8CF823A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/69b9ddd5fec2c8bfcb05caa617d4c5b1ca567f01/ghc >--------------------------------------------------------------- commit 69b9ddd5fec2c8bfcb05caa617d4c5b1ca567f01 Author: Ben Gamari Date: Wed May 17 23:42:59 2017 -0400 Debug >--------------------------------------------------------------- 69b9ddd5fec2c8bfcb05caa617d4c5b1ca567f01 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 Jul 27 20:48:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:30 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Parametrize on make command (d89dbdf) Message-ID: <20170727204830.D16BC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d89dbdf6ecf130c1db4305480a3bc1096d450736/ghc >--------------------------------------------------------------- commit d89dbdf6ecf130c1db4305480a3bc1096d450736 Author: Ben Gamari Date: Mon May 29 15:44:39 2017 -0400 Parametrize on make command >--------------------------------------------------------------- d89dbdf6ecf130c1db4305480a3bc1096d450736 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 Thu Jul 27 20:48:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:39 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix Windows PATHs (90b9ea1) Message-ID: <20170727204839.043323A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/90b9ea1b5af4a3f6408f839e4d59976c0ab1cfa9/ghc >--------------------------------------------------------------- commit 90b9ea1b5af4a3f6408f839e4d59976c0ab1cfa9 Author: Ben Gamari Date: Mon May 29 16:31:28 2017 -0400 Fix Windows PATHs >--------------------------------------------------------------- 90b9ea1b5af4a3f6408f839e4d59976c0ab1cfa9 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 Thu Jul 27 20:48:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:41 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (5008e3e) Message-ID: <20170727204841.B4B2B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/5008e3e0e6dd7f2b9f81ef97221f38b373b5aa3c/ghc >--------------------------------------------------------------- commit 5008e3e0e6dd7f2b9f81ef97221f38b373b5aa3c Author: Ben Gamari Date: Thu May 18 02:59:40 2017 -0400 Debug >--------------------------------------------------------------- 5008e3e0e6dd7f2b9f81ef97221f38b373b5aa3c 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 Jul 27 20:48:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:47 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring, add Windows, fix cross (cba9eff) Message-ID: <20170727204847.2D1493A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/cba9eff7dcdd479c1abe691be3828bb896dd041b/ghc >--------------------------------------------------------------- commit cba9eff7dcdd479c1abe691be3828bb896dd041b Author: Ben Gamari Date: Thu May 18 02:14:40 2017 -0400 Refactoring, add Windows, fix cross >--------------------------------------------------------------- cba9eff7dcdd479c1abe691be3828bb896dd041b 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 Jul 27 20:48:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:44 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Checkout (5f72d8a) Message-ID: <20170727204844.723983A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/5f72d8ac40468e856c0bef0f5cfce42caa5893d9/ghc >--------------------------------------------------------------- commit 5f72d8ac40468e856c0bef0f5cfce42caa5893d9 Author: Ben Gamari Date: Thu May 18 01:19:52 2017 -0400 Checkout >--------------------------------------------------------------- 5f72d8ac40468e856c0bef0f5cfce42caa5893d9 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 Jul 27 20:48:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:49 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Run jobs in parallel (defc512) Message-ID: <20170727204849.D85BC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/defc51238835aa5a2ce1f84cb80a2108e85a8d1b/ghc >--------------------------------------------------------------- commit defc51238835aa5a2ce1f84cb80a2108e85a8d1b Author: Ben Gamari Date: Wed May 17 23:34:37 2017 -0400 Run jobs in parallel >--------------------------------------------------------------- defc51238835aa5a2ce1f84cb80a2108e85a8d1b 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 Jul 27 20:48:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:52 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rework handling of Windows (7ae74fc) Message-ID: <20170727204852.911233A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7ae74fc657091049f593498229a7f0c8d98123c7/ghc >--------------------------------------------------------------- commit 7ae74fc657091049f593498229a7f0c8d98123c7 Author: Ben Gamari Date: Mon May 29 13:08:49 2017 -0400 Rework handling of Windows >--------------------------------------------------------------- 7ae74fc657091049f593498229a7f0c8d98123c7 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 Thu Jul 27 20:48:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:55 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Nailed the Windows issue (ba8a4c5) Message-ID: <20170727204855.4CA6D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ba8a4c51b2050b8050306bb58552e41389ffc3f5/ghc >--------------------------------------------------------------- commit ba8a4c51b2050b8050306bb58552e41389ffc3f5 Author: Ben Gamari Date: Mon May 29 12:48:34 2017 -0400 Nailed the Windows issue >--------------------------------------------------------------- ba8a4c51b2050b8050306bb58552e41389ffc3f5 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 Thu Jul 27 20:48:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:48:58 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Move to scripted pipeline (4902e35) Message-ID: <20170727204858.074283A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/4902e3593983d3fc1e329ce1ad882d6e40f1ee13/ghc >--------------------------------------------------------------- commit 4902e3593983d3fc1e329ce1ad882d6e40f1ee13 Author: Ben Gamari Date: Wed May 17 20:52:58 2017 -0400 Move to scripted pipeline >--------------------------------------------------------------- 4902e3593983d3fc1e329ce1ad882d6e40f1ee13 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 Jul 27 20:49:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:00 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add THREADS parameter (194a78b) Message-ID: <20170727204900.B97AB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/194a78b8276396fd5d746313389f0e2621f4d577/ghc >--------------------------------------------------------------- commit 194a78b8276396fd5d746313389f0e2621f4d577 Author: Ben Gamari Date: Sat May 13 11:59:37 2017 -0400 Add THREADS parameter >--------------------------------------------------------------- 194a78b8276396fd5d746313389f0e2621f4d577 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 Jul 27 20:49:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:03 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Use archiveArtifacts instead of archive (b600c2f) Message-ID: <20170727204903.7F5223A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/b600c2fda718949fed2bc144b0b6024014be1e44/ghc >--------------------------------------------------------------- commit b600c2fda718949fed2bc144b0b6024014be1e44 Author: Ben Gamari Date: Mon May 29 15:44:56 2017 -0400 Use archiveArtifacts instead of archive >--------------------------------------------------------------- b600c2fda718949fed2bc144b0b6024014be1e44 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 Thu Jul 27 20:49:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:06 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Reformat (7f6a9cf) Message-ID: <20170727204906.3CCBF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7f6a9cfa35874a89f7d47785641f6824fc58f159/ghc >--------------------------------------------------------------- commit 7f6a9cfa35874a89f7d47785641f6824fc58f159 Author: Ben Gamari Date: Thu May 18 02:58:05 2017 -0400 Reformat >--------------------------------------------------------------- 7f6a9cfa35874a89f7d47785641f6824fc58f159 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 Jul 27 20:49:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:09 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Testing simpler Jenkinsfile (9603015) Message-ID: <20170727204909.7BDF83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9603015411aa0e8d5ea0c75b40584d636f696b48/ghc >--------------------------------------------------------------- commit 9603015411aa0e8d5ea0c75b40584d636f696b48 Author: Ben Gamari Date: Fri Apr 21 14:29:34 2017 -0400 Testing simpler Jenkinsfile >--------------------------------------------------------------- 9603015411aa0e8d5ea0c75b40584d636f696b48 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 Thu Jul 27 20:49:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:12 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Don't run nofib on Windows (dd50a91) Message-ID: <20170727204912.4BF803A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/dd50a91e031c08c6ca7b50964905b9e7410c5f67/ghc >--------------------------------------------------------------- commit dd50a91e031c08c6ca7b50964905b9e7410c5f67 Author: Ben Gamari Date: Mon May 29 16:14:11 2017 -0400 Don't run nofib on Windows >--------------------------------------------------------------- dd50a91e031c08c6ca7b50964905b9e7410c5f67 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 Thu Jul 27 20:49:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:15 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (95ae236) Message-ID: <20170727204915.0AEAC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/95ae23656b2b3ec3a4a84b622984d38cacfb6e15/ghc >--------------------------------------------------------------- commit 95ae23656b2b3ec3a4a84b622984d38cacfb6e15 Author: Ben Gamari Date: Mon May 29 15:49:33 2017 -0400 Debug >--------------------------------------------------------------- 95ae23656b2b3ec3a4a84b622984d38cacfb6e15 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 Thu Jul 27 20:49:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:17 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: More things (5883de5) Message-ID: <20170727204917.B98833A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/5883de5c39f4e91cce7f8e22288f461abfc7b7cd/ghc >--------------------------------------------------------------- commit 5883de5c39f4e91cce7f8e22288f461abfc7b7cd Author: Ben Gamari Date: Thu May 18 01:38:55 2017 -0400 More things >--------------------------------------------------------------- 5883de5c39f4e91cce7f8e22288f461abfc7b7cd 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 Jul 27 20:49:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:20 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Testing (31a94bb) Message-ID: <20170727204920.77DD13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/31a94bb3476750ed49e6afedd62814aee5ba89fc/ghc >--------------------------------------------------------------- commit 31a94bb3476750ed49e6afedd62814aee5ba89fc Author: Ben Gamari Date: Fri Apr 28 09:53:13 2017 -0400 Testing >--------------------------------------------------------------- 31a94bb3476750ed49e6afedd62814aee5ba89fc 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 Thu Jul 27 20:49:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:23 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: windows (d622e6d) Message-ID: <20170727204923.32BD93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d622e6d43f4ca92dfd690f9b5dc2ace6b8d8ffde/ghc >--------------------------------------------------------------- commit d622e6d43f4ca92dfd690f9b5dc2ace6b8d8ffde Author: Ben Gamari Date: Thu May 18 01:55:46 2017 -0400 windows >--------------------------------------------------------------- d622e6d43f4ca92dfd690f9b5dc2ace6b8d8ffde 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 Jul 27 20:49:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:25 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Cross (318f9da) Message-ID: <20170727204925.E18E13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/318f9da2830c59489c6a0308e589f021b2bdb395/ghc >--------------------------------------------------------------- commit 318f9da2830c59489c6a0308e589f021b2bdb395 Author: Ben Gamari Date: Thu May 18 01:00:42 2017 -0400 Cross >--------------------------------------------------------------- 318f9da2830c59489c6a0308e589f021b2bdb395 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 Jul 27 20:49:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:28 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Ensure that carch, prefix, and ghcPath are in scope (aae4b7d) Message-ID: <20170727204928.9CFD73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/aae4b7d8b216d6e82c983ec20c8429cb115c85cd/ghc >--------------------------------------------------------------- commit aae4b7d8b216d6e82c983ec20c8429cb115c85cd Author: Ben Gamari Date: Mon Jun 12 16:31:31 2017 -0400 Ensure that carch, prefix, and ghcPath are in scope >--------------------------------------------------------------- aae4b7d8b216d6e82c983ec20c8429cb115c85cd Jenkinsfile | 1 + 1 file changed, 1 insertion(+) diff --git a/Jenkinsfile b/Jenkinsfile index 9c2123d..98e0946 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -110,6 +110,7 @@ if (params.runNofib) { def withMingw(String msystem, Closure f) { // Derived from msys2's /etc/msystem def msysRoot = 'C:\\msys64' + String carch, prefix, ghcPath if (msystem == 'MINGW32') { prefix = "${msysRoot}\\mingw32" carch = 'i686' From git at git.haskell.org Thu Jul 27 20:49:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:31 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix test (c79a5da) Message-ID: <20170727204931.57F993A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c79a5da15f489efe8b32dbf279099b6d3150a06a/ghc >--------------------------------------------------------------- commit c79a5da15f489efe8b32dbf279099b6d3150a06a Author: Ben Gamari Date: Tue May 30 13:57:23 2017 -0400 Fix test >--------------------------------------------------------------- c79a5da15f489efe8b32dbf279099b6d3150a06a 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 Thu Jul 27 20:49:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:34 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Pass BINDIST to make test (5bba8db) Message-ID: <20170727204934.188533A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/5bba8dbb1cb9aff085752a7d1663fdc75cb6467f/ghc >--------------------------------------------------------------- commit 5bba8dbb1cb9aff085752a7d1663fdc75cb6467f Author: Ben Gamari Date: Mon Jun 5 13:15:45 2017 -0400 Pass BINDIST to make test >--------------------------------------------------------------- 5bba8dbb1cb9aff085752a7d1663fdc75cb6467f Jenkinsfile | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index a051d7c..7abcc9d 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,9 +1,11 @@ #!groovy /* - Dependencies: + Jenkins dependencies: * Pipeline Utility steps plugin + Linux (Debian) worker dependencies: + * xutil-dev curl automake autoconf libtool python3 python3-sphinx, llvm-4.0 */ import net.sf.json.JSONObject @@ -271,8 +273,8 @@ def testGhc(params) { if (params.nightly) { target = 'slowtest' } - sh "${makeCmd} -Ctestsuite/tests stage=2 LOCAL=0 THREADS=${env.THREADS} ${target}" - sh "${makeCmd} -Ctestsuite/tests/stage1 stage=1 LOCAL=0 THREADS=${env.THREADS} ${target}" + sh "${makeCmd} -Ctestsuite/tests stage=2 LOCAL=0 BINDIST=YES THREADS=${env.THREADS} ${target}" + sh "${makeCmd} -Ctestsuite/tests/stage1 stage=1 LOCAL=0 BINDIST=YES THREADS=${env.THREADS} ${target}" } stage('Run nofib') { From git at git.haskell.org Thu Jul 27 20:49:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:36 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Enable win64 again (e1702b6) Message-ID: <20170727204936.CB4463A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/e1702b62e3c53060a3483b5b340b26c378211d2c/ghc >--------------------------------------------------------------- commit e1702b62e3c53060a3483b5b340b26c378211d2c Author: Ben Gamari Date: Mon Jun 19 12:39:58 2017 -0400 Enable win64 again >--------------------------------------------------------------- e1702b62e3c53060a3483b5b340b26c378211d2c Jenkinsfile | 2 -- 1 file changed, 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index a808fcd..bcf3faa 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -83,13 +83,11 @@ parallel ( } }, // Requires cygpath plugin? - /* "windows 64" : { node(label: 'windows && amd64') { withMingw('MINGW64') { buildAndTestGhc(targetTriple: 'x86_64-w64-mingw32') } } }, - */ "windows 32" : { node(label: 'windows && amd64') { withMingw('MINGW32') { buildAndTestGhc(targetTriple: 'x86_64-pc-msys') } From git at git.haskell.org Thu Jul 27 20:49:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:39 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix quoting of carch (7f648a2) Message-ID: <20170727204939.87CE13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7f648a28b7d2c1babc1bb86ccfa548072a41fcbd/ghc >--------------------------------------------------------------- commit 7f648a28b7d2c1babc1bb86ccfa548072a41fcbd Author: Ben Gamari Date: Mon Jun 12 16:40:33 2017 -0400 Fix quoting of carch >--------------------------------------------------------------- 7f648a28b7d2c1babc1bb86ccfa548072a41fcbd Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 98e0946..9f87698 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -122,7 +122,7 @@ def withMingw(String msystem, Closure f) { } else { fail } - chost = '${carch}-w64-mingw32' + chost = "${carch}-w64-mingw32" withEnv(["MSYSTEM=${msystem}", "PATH+mingw=${prefix}\\bin", From git at git.haskell.org Thu Jul 27 20:49:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:42 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (04ee922) Message-ID: <20170727204942.451AD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/04ee922be710b5dd16984a402ccb13d310379e94/ghc >--------------------------------------------------------------- commit 04ee922be710b5dd16984a402ccb13d310379e94 Author: Ben Gamari Date: Sun Jun 4 11:18:23 2017 -0400 Debug >--------------------------------------------------------------- 04ee922be710b5dd16984a402ccb13d310379e94 Jenkinsfile | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index a1a6b13..c924e85 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -223,8 +223,9 @@ def withGhcSrcDist(Closure f) { } def metadata = readJSON file: 'src-dist.json' + sh "cat src-dist.json" echo "${metadata}" - sh "${metadata.dirName}" + sh "echo ${metadata.dirName}; ls ${metadata.dirName}" dir(metadata.dirName) { f() } From git at git.haskell.org Thu Jul 27 20:49:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:44 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix configure arguments (4206227) Message-ID: <20170727204944.F2AA53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/4206227926c9a1d38719ff0f9f7351606589fa2c/ghc >--------------------------------------------------------------- commit 4206227926c9a1d38719ff0f9f7351606589fa2c Author: Ben Gamari Date: Mon May 29 22:55:51 2017 -0400 Fix configure arguments >--------------------------------------------------------------- 4206227926c9a1d38719ff0f9f7351606589fa2c 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 Thu Jul 27 20:49:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:47 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Various accumulated fixes (e41f597) Message-ID: <20170727204947.AE6CA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/e41f5971ce50d977e57e379c05d808b38991616d/ghc >--------------------------------------------------------------- commit e41f5971ce50d977e57e379c05d808b38991616d Author: Ben Gamari Date: Tue Jun 27 17:31:58 2017 -0400 Various accumulated fixes >--------------------------------------------------------------- e41f5971ce50d977e57e379c05d808b38991616d Jenkinsfile | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index bcf3faa..fee5743 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -6,6 +6,10 @@ Linux (Debian) worker dependencies: * xutil-dev curl automake autoconf libtool python3 python3-sphinx, llvm-4.0 + + Requires approvals for: + * new net.sf.json.JSONObject + */ import net.sf.json.JSONObject @@ -123,7 +127,7 @@ def withMingw(String msystem, Closure f) { } else { fail } - chost = "${carch}-w64-mingw32" + String chost = "${carch}-w64-mingw32" withEnv(["MSYSTEM=${msystem}", "PATH+mingw=${prefix}\\bin", @@ -133,7 +137,7 @@ def withMingw(String msystem, Closure f) { "MSYSTEM_CHOST=${chost}", "MINGW_CHOST=${chost}", "MINGW_PREFIX=${prefix}", - "MINGW_PACKAGE_PREFIX=mingw-w64-${MSYSTEM_CARCH}", + "MINGW_PACKAGE_PREFIX=mingw-w64-${carch}", "CONFIG_SITE=${prefix}/etc/config.site" ], f) } @@ -202,7 +206,7 @@ def buildGhc(params) { sh "${makeCmd} binary-dist" def json = new JSONObject() def tarPath = getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') - def tarName = sh(script: "basename ${tarPath}", returnStdout: true) + def tarName = sh(script: "basename ${tarPath}", returnStdout: true).trim() json.put('tarName', tarName) json.put('dirName', getMakeValue(makeCmd, 'BIN_DIST_NAME')) json.put('ghcVersion', getMakeValue(makeCmd, 'ProjectVersion')) From git at git.haskell.org Thu Jul 27 20:49:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:50 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix GHC path (9c60958) Message-ID: <20170727204950.6E0933A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9c60958965c29be1b428045648d02617e4e9cb3f/ghc >--------------------------------------------------------------- commit 9c60958965c29be1b428045648d02617e4e9cb3f Author: Ben Gamari Date: Tue Jun 13 00:44:15 2017 -0400 Fix GHC path >--------------------------------------------------------------- 9c60958965c29be1b428045648d02617e4e9cb3f Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 24810c5..486e975 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -114,7 +114,7 @@ def withMingw(String msystem, Closure f) { if (msystem == 'MINGW32') { prefix = "${msysRoot}\\mingw32" carch = 'i686' - ghcPath = '$HOME/ghc-8.0.2-i386/bin' + ghcPath = '$HOME/ghc-8.0.1-i386/bin' } else if (msystem == 'MINGW64') { prefix = "${msysRoot}\\mingw64" carch = 'x86_64' From git at git.haskell.org Thu Jul 27 20:49:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:53 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (ac4fa1f) Message-ID: <20170727204953.28B6C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ac4fa1f5833a28e2ea2966c07e72749fdceba931/ghc >--------------------------------------------------------------- commit ac4fa1f5833a28e2ea2966c07e72749fdceba931 Author: Ben Gamari Date: Wed May 31 14:57:34 2017 -0400 Debug >--------------------------------------------------------------- ac4fa1f5833a28e2ea2966c07e72749fdceba931 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 Thu Jul 27 20:49:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:55 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Don't try to record commit of bindist (2f87ce7) Message-ID: <20170727204955.DAC5F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2f87ce74bc845960acb64a48eab490be66f0b6ff/ghc >--------------------------------------------------------------- commit 2f87ce74bc845960acb64a48eab490be66f0b6ff Author: Ben Gamari Date: Mon Jun 5 15:31:26 2017 -0400 Don't try to record commit of bindist >--------------------------------------------------------------- 2f87ce74bc845960acb64a48eab490be66f0b6ff Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index adf8058..9a098e0 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -45,6 +45,7 @@ stage("Build source distribution") { def json = new JSONObject() json.put('dirName', "ghc-${version}" as String) + json.put('commit', resolveCommitSha('HEAD')) writeJSON(file: 'src-dist.json', json: json) stash(name: 'source-dist', includes: 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz,src-dist.json') @@ -191,7 +192,6 @@ def buildGhc(params) { def json = new JSONObject() def tarPath = getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') def tarName = sh(script: "basename ${tarPath}", returnStdout: true) - json.put('commit', resolveCommitSha('HEAD')) json.put('tarName', tarName) json.put('dirName', getMakeValue(makeCmd, 'BIN_DIST_NAME')) json.put('ghcVersion', getMakeValue(makeCmd, 'ProjectVersion')) From git at git.haskell.org Thu Jul 27 20:49:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:49:58 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Introduce echo! make target (9058d44) Message-ID: <20170727204958.982DC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9058d44583c623de5bff6cdeee8904f2bc92a820/ghc >--------------------------------------------------------------- commit 9058d44583c623de5bff6cdeee8904f2bc92a820 Author: Ben Gamari Date: Sun Jun 4 10:27:24 2017 -0400 Introduce echo! make target This is analogous to show! >--------------------------------------------------------------- 9058d44583c623de5bff6cdeee8904f2bc92a820 Makefile | 4 ++++ ghc.mk | 4 ++++ 2 files changed, 8 insertions(+) diff --git a/Makefile b/Makefile index 9b888e7..4863cd7 100644 --- a/Makefile +++ b/Makefile @@ -167,6 +167,10 @@ $(filter clean_%, $(MAKECMDGOALS)) : clean_% : bootstrapping-files show echo: $(MAKE) --no-print-directory -f ghc.mk $@ +.PHONY: echo! +echo!: + @$(MAKE) --no-print-directory -f ghc.mk echo NO_INCLUDE_PKGDATA=YES + .PHONY: show! show!: $(MAKE) --no-print-directory -f ghc.mk show NO_INCLUDE_PKGDATA=YES diff --git a/ghc.mk b/ghc.mk index 4eb1658..b3410ac 100644 --- a/ghc.mk +++ b/ghc.mk @@ -260,6 +260,10 @@ ifeq "$(findstring show,$(MAKECMDGOALS))" "show" NO_INCLUDE_DEPS = YES # We want package-data.mk for show endif +ifeq "$(findstring echo,$(MAKECMDGOALS))" "echo" +NO_INCLUDE_DEPS = YES +# We want package-data.mk for show +endif # ----------------------------------------------------------------------------- # Ways From git at git.haskell.org Thu Jul 27 20:50:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:01 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: No need to boot (6645762) Message-ID: <20170727205001.56C4B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/664576291c9d0e8b481b5ac1adf2e518ba54752e/ghc >--------------------------------------------------------------- commit 664576291c9d0e8b481b5ac1adf2e518ba54752e Author: Ben Gamari Date: Sun Jun 4 10:54:49 2017 -0400 No need to boot >--------------------------------------------------------------- 664576291c9d0e8b481b5ac1adf2e518ba54752e Jenkinsfile | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index b7c9db5..410a86d 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -29,7 +29,10 @@ stage("Build source distribution") { """ } stage("Configuring tree") { - sh "./configure" + sh """ + ./boot + ./configure + """ } stage("Build tarballs") { def version = getMakeValue('make', 'ProjectVersion') @@ -162,10 +165,7 @@ def buildGhc(params) { if (unreg) { configure_opts += '--enable-unregisterised' } - sh """ - ./boot - ./configure ${configure_opts.join(' ')} - """ + sh "./configure ${configure_opts.join(' ')}" } stage('Build') { From git at git.haskell.org Thu Jul 27 20:50:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:04 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Ugh, sh not echo (ab5ca7d) Message-ID: <20170727205004.12BE83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ab5ca7dc6799d1516e9032745d6ef55ab9e86d34/ghc >--------------------------------------------------------------- commit ab5ca7dc6799d1516e9032745d6ef55ab9e86d34 Author: Ben Gamari Date: Sun Jun 18 09:35:42 2017 -0400 Ugh, sh not echo >--------------------------------------------------------------- ab5ca7dc6799d1516e9032745d6ef55ab9e86d34 Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 451a3a5..d559f06 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -155,7 +155,7 @@ def buildGhc(params) { withGhcSrcDist() { stage('Configure') { - echo 'echo $PATH' + sh 'echo $PATH' sh "which ghc" def speed = 'NORMAL' From git at git.haskell.org Thu Jul 27 20:50:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:06 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Run stage1 tests as well (ac4da99) Message-ID: <20170727205006.C0CBF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ac4da99a5a98f3c36de152a169166fc73ee6db21/ghc >--------------------------------------------------------------- commit ac4da99a5a98f3c36de152a169166fc73ee6db21 Author: Ben Gamari Date: Sun Jun 4 21:24:15 2017 -0400 Run stage1 tests as well >--------------------------------------------------------------- ac4da99a5a98f3c36de152a169166fc73ee6db21 Jenkinsfile | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index c369979..a051d7c 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -271,7 +271,8 @@ def testGhc(params) { if (params.nightly) { target = 'slowtest' } - sh "${makeCmd} THREADS=${env.THREADS} ${target}" + sh "${makeCmd} -Ctestsuite/tests stage=2 LOCAL=0 THREADS=${env.THREADS} ${target}" + sh "${makeCmd} -Ctestsuite/tests/stage1 stage=1 LOCAL=0 THREADS=${env.THREADS} ${target}" } stage('Run nofib') { From git at git.haskell.org Thu Jul 27 20:50:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:09 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Handle testsuite on Windows (9e9481c) Message-ID: <20170727205009.7D3383A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9e9481c9b598ec24ff19ff35eb55aef38cdb6b22/ghc >--------------------------------------------------------------- commit 9e9481c9b598ec24ff19ff35eb55aef38cdb6b22 Author: Ben Gamari Date: Sat Jun 17 22:53:30 2017 -0400 Handle testsuite on Windows >--------------------------------------------------------------- 9e9481c9b598ec24ff19ff35eb55aef38cdb6b22 Jenkinsfile | 11 ++++++++--- 1 file changed, 8 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 179421e..b754745 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -265,16 +265,21 @@ def withGhcBinDist(String targetTriple, Closure f) { def testGhc(params) { String targetTriple = params?.targetTriple // See Note [Spaces in TEST_HC] - String instDir="bindisttest/install dir" String testGhc="${instDir}/bin/ghc" String makeCmd = params?.makeCmd ?: 'make' + String instDir="${pwd()}/bindisttest/install dir" withGhcBinDist(targetTriple) { stage('Configure') { echo 'echo $PATH' sh "which ghc" - sh "./configure --prefix=\"`pwd`/${instDir}\"" - sh "${makeCmd} install" + if (isUnix()) { + sh "./configure --prefix=\"${instDir}\"" + sh "${makeCmd} install" + } else { + sh "mkdir -p \"${instDir}\"" + sh "cp -R * ${instDir}" + } } stage('Install testsuite dependencies') { From git at git.haskell.org Thu Jul 27 20:50:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:12 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix ghc path (9d8e9fa) Message-ID: <20170727205012.3955C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9d8e9fae70309cbfdae5766eb0f6d691fac68384/ghc >--------------------------------------------------------------- commit 9d8e9fae70309cbfdae5766eb0f6d691fac68384 Author: Ben Gamari Date: Wed Jun 28 08:53:54 2017 -0400 Fix ghc path >--------------------------------------------------------------- 9d8e9fae70309cbfdae5766eb0f6d691fac68384 Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index c135b9d..b1b1d4d 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -302,7 +302,7 @@ def testGhc(params) { if (params.nightly) { target = 'slowtest' } - sh "${makeCmd} -Ctestsuite/tests LOCAL=0 BINDIST=YES THREADS=${env.THREADS} TEST_HC=\"`pwd`/${testGhc}\" ${target}" + sh "${makeCmd} -Ctestsuite/tests LOCAL=0 BINDIST=YES THREADS=${env.THREADS} TEST_HC=\"${testGhc}\" ${target}" } } } From git at git.haskell.org Thu Jul 27 20:50:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:14 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: No trailing newline (698bdd7) Message-ID: <20170727205014.E782B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/698bdd7c8dc77ebc704df01ff593c91851cfe764/ghc >--------------------------------------------------------------- commit 698bdd7c8dc77ebc704df01ff593c91851cfe764 Author: Ben Gamari Date: Mon Jun 19 07:27:07 2017 -0400 No trailing newline >--------------------------------------------------------------- 698bdd7c8dc77ebc704df01ff593c91851cfe764 Jenkinsfile | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 9aac44f..a808fcd 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -83,11 +83,13 @@ parallel ( } }, // Requires cygpath plugin? + /* "windows 64" : { node(label: 'windows && amd64') { withMingw('MINGW64') { buildAndTestGhc(targetTriple: 'x86_64-w64-mingw32') } } }, + */ "windows 32" : { node(label: 'windows && amd64') { withMingw('MINGW32') { buildAndTestGhc(targetTriple: 'x86_64-pc-msys') } @@ -109,9 +111,9 @@ if (params.runNofib) { def withMingw(String msystem, Closure f) { // Derived from msys2's /etc/msystem - def msysRoot = 'C:\\msys64' + String msysRoot = 'C:\\msys64' String carch, prefix, ghcPath - home = sh(script: 'echo $HOME', returnStdout: true) + home = sh(script: 'echo -n $HOME', returnStdout: true) if (msystem == 'MINGW32') { prefix = "${msysRoot}\\mingw32" carch = 'i686' From git at git.haskell.org Thu Jul 27 20:50:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:17 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix JSON serialization (a58956c) Message-ID: <20170727205017.A05923A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a58956c5137973e570ece65bfbc500d99f9ffb8f/ghc >--------------------------------------------------------------- commit a58956c5137973e570ece65bfbc500d99f9ffb8f Author: Ben Gamari Date: Wed May 31 10:43:24 2017 -0400 Fix JSON serialization >--------------------------------------------------------------- a58956c5137973e570ece65bfbc500d99f9ffb8f 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 Thu Jul 27 20:50:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:20 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Be more explicit (8deb4cb) Message-ID: <20170727205020.62F003A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/8deb4cb3fd19f76eba006c82ae7bc8810a4a6451/ghc >--------------------------------------------------------------- commit 8deb4cb3fd19f76eba006c82ae7bc8810a4a6451 Author: Ben Gamari Date: Tue May 30 16:04:31 2017 -0400 Be more explicit >--------------------------------------------------------------- 8deb4cb3fd19f76eba006c82ae7bc8810a4a6451 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 Thu Jul 27 20:50:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:23 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Disable non-Windows builds (394772b) Message-ID: <20170727205023.22B423A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/394772b621796d28c321e9514f29625b2260f99c/ghc >--------------------------------------------------------------- commit 394772b621796d28c321e9514f29625b2260f99c Author: Ben Gamari Date: Mon May 29 19:34:11 2017 -0400 Disable non-Windows builds >--------------------------------------------------------------- 394772b621796d28c321e9514f29625b2260f99c 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 Thu Jul 27 20:50:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:25 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Properly quote instDir (9ec5442) Message-ID: <20170727205025.CD83F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9ec544279cb9d2ebc0651244b59167a03487581c/ghc >--------------------------------------------------------------- commit 9ec544279cb9d2ebc0651244b59167a03487581c Author: Ben Gamari Date: Thu Jun 29 08:58:04 2017 -0400 Properly quote instDir >--------------------------------------------------------------- 9ec544279cb9d2ebc0651244b59167a03487581c Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index b1b1d4d..ab92bfe 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -284,7 +284,7 @@ def testGhc(params) { sh "${makeCmd} install" } else { sh "mkdir -p \"${instDir}\"" - sh "cp -R * ${instDir}" + sh "cp -R * \"${instDir}\"" } } From git at git.haskell.org Thu Jul 27 20:50:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:28 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Use named argument list (4fe8d91) Message-ID: <20170727205028.8E8F53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/4fe8d9198c550fbacc69a6ec588563df408e3b7a/ghc >--------------------------------------------------------------- commit 4fe8d9198c550fbacc69a6ec588563df408e3b7a Author: Ben Gamari Date: Mon Jun 5 13:27:27 2017 -0400 Use named argument list >--------------------------------------------------------------- 4fe8d9198c550fbacc69a6ec588563df408e3b7a Jenkinsfile | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 7abcc9d..6fc89ae 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -193,7 +193,7 @@ def buildGhc(params) { writeJSON(file: 'bindist.json', json: 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}" + archiveArtifacts artifacts: tarName } } } @@ -286,7 +286,7 @@ def testGhc(params) { ${makeCmd} boot ${makeCmd} >../nofib.log 2>&1 """ - archiveArtifacts 'nofib.log' + archiveArtifacts artifacts: 'nofib.log' } } } From git at git.haskell.org Thu Jul 27 20:50:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:31 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debuggging (2aaf460) Message-ID: <20170727205031.4C2463A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2aaf46062806e57a225bfb6c20e92d7469b05a8f/ghc >--------------------------------------------------------------- commit 2aaf46062806e57a225bfb6c20e92d7469b05a8f Author: Ben Gamari Date: Sun Jun 4 11:12:23 2017 -0400 Debuggging >--------------------------------------------------------------- 2aaf46062806e57a225bfb6c20e92d7469b05a8f Jenkinsfile | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 59daa63..a1a6b13 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -223,6 +223,8 @@ def withGhcSrcDist(Closure f) { } def metadata = readJSON file: 'src-dist.json' + echo "${metadata}" + sh "${metadata.dirName}" dir(metadata.dirName) { f() } @@ -237,7 +239,7 @@ def withGhcBinDist(String targetTriple, Closure f) { echo "${metadata}" sh "tar -xf ${metadata.tarName}" sh "tar -xf ghc-testsuite.tar.xz" - dir("${metadata.dirName}") { + dir(metadata.dirName) { try { f() } finally { From git at git.haskell.org Thu Jul 27 20:50:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:34 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix documentation (8ce55fb) Message-ID: <20170727205034.08FB23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/8ce55fbbff9ceb3ec559d7d6cd178fe3c35c706d/ghc >--------------------------------------------------------------- commit 8ce55fbbff9ceb3ec559d7d6cd178fe3c35c706d Author: Ben Gamari Date: Tue May 30 10:45:52 2017 -0400 Fix documentation >--------------------------------------------------------------- 8ce55fbbff9ceb3ec559d7d6cd178fe3c35c706d 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 Thu Jul 27 20:50:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:36 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Clean up treatment of tests (9390d4d) Message-ID: <20170727205036.BA5AE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9390d4db05e4e708ea271d676a918b7c6c834f52/ghc >--------------------------------------------------------------- commit 9390d4db05e4e708ea271d676a918b7c6c834f52 Author: Ben Gamari Date: Tue May 30 01:10:56 2017 -0400 Clean up treatment of tests >--------------------------------------------------------------- 9390d4db05e4e708ea271d676a918b7c6c834f52 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 Thu Jul 27 20:50:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:39 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Kill debug output (16e7d1b) Message-ID: <20170727205039.745393A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/16e7d1ba3d0c40762541f13ac4e0fcefb4563684/ghc >--------------------------------------------------------------- commit 16e7d1ba3d0c40762541f13ac4e0fcefb4563684 Author: Ben Gamari Date: Wed Jun 14 16:55:46 2017 -0400 Kill debug output >--------------------------------------------------------------- 16e7d1ba3d0c40762541f13ac4e0fcefb4563684 Jenkinsfile | 1 - 1 file changed, 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 1c6fa39..25ad7f1 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -239,7 +239,6 @@ def withGhcSrcDist(Closure f) { } def metadata = readJSON file: 'src-dist.json' - sh "cat src-dist.json" dir(metadata.dirName) { f() } From git at git.haskell.org Thu Jul 27 20:50:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:42 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Reenable everything else (61c7edb) Message-ID: <20170727205042.2FF7B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/61c7edbc564c9bdee7a76d6426153fa039bd159f/ghc >--------------------------------------------------------------- commit 61c7edbc564c9bdee7a76d6426153fa039bd159f Author: Ben Gamari Date: Mon May 29 22:45:19 2017 -0400 Reenable everything else >--------------------------------------------------------------- 61c7edbc564c9bdee7a76d6426153fa039bd159f 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 Thu Jul 27 20:50:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:44 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Try adding type annotation (05e7d5d) Message-ID: <20170727205044.E06E93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/05e7d5d862ef6d4faec34571bb9d7920a19ce069/ghc >--------------------------------------------------------------- commit 05e7d5d862ef6d4faec34571bb9d7920a19ce069 Author: Ben Gamari Date: Sun Jun 4 11:26:54 2017 -0400 Try adding type annotation >--------------------------------------------------------------- 05e7d5d862ef6d4faec34571bb9d7920a19ce069 Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index c924e85..bad87bf 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -196,7 +196,7 @@ def buildGhc(params) { } } -def getMakeValue(String makeCmd, String value) { +String getMakeValue(String makeCmd, String value) { return sh(script: "${makeCmd} -s echo! VALUE=${value}", returnStdout: true) } From git at git.haskell.org Thu Jul 27 20:50:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:47 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: No need to configure (a469010) Message-ID: <20170727205047.9956E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a46901070b474e6de94b2d27b4c03e544800ab4d/ghc >--------------------------------------------------------------- commit a46901070b474e6de94b2d27b4c03e544800ab4d Author: Ben Gamari Date: Sun Jun 4 10:47:30 2017 -0400 No need to configure >--------------------------------------------------------------- a46901070b474e6de94b2d27b4c03e544800ab4d Jenkinsfile | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index d2f39f3..6615265 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -29,10 +29,7 @@ stage("Build source distribution") { """ } stage("Configuring tree") { - sh """ - ./boot - ./configure - """ + sh "./configure" } stage("Build tarballs") { def version = getMakeValue('make', 'ProjectVersion') From git at git.haskell.org Thu Jul 27 20:50:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:50 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix windows paths (eb9c0b5) Message-ID: <20170727205050.534833A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/eb9c0b533f1f9b961f5b72ba9687bed9e446194f/ghc >--------------------------------------------------------------- commit eb9c0b533f1f9b961f5b72ba9687bed9e446194f Author: Ben Gamari Date: Fri Jun 9 13:50:09 2017 -0400 Fix windows paths >--------------------------------------------------------------- eb9c0b533f1f9b961f5b72ba9687bed9e446194f Jenkinsfile | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 9a098e0..acaf373 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -108,18 +108,21 @@ def withMingw(String msystem, Closure f) { // Derived from msys2's /etc/msystem def msysRoot = 'C:\\msys64' if (msystem == 'MINGW32') { - prefix = '${msysRoot}\\mingw32' + prefix = "${msysRoot}\\mingw32" carch = 'i686' + ghcPath = '$HOME/ghc-8.0.2-i386/bin' } else if (msystem == 'MINGW64') { - prefix = '${msysRoot}\\mingw64' + prefix = "${msysRoot}\\mingw64" carch = 'x86_64' + ghcPath = '$HOME/ghc-8.0.2-x86_64/bin' } 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", + "PATH+mingw=${prefix}\\bin", + "PATH+ghc=${ghcPath}", "MSYSTEM_PREFIX=${prefix}", "MSYSTEM_CARCH=${carch}", "MSYSTEM_CHOST=${chost}", From git at git.haskell.org Thu Jul 27 20:50:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:53 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Don't use deleteDir (c1aabd5) Message-ID: <20170727205053.0D83D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c1aabd5dbd902ed848b7c00c5e8927e3006f8314/ghc >--------------------------------------------------------------- commit c1aabd5dbd902ed848b7c00c5e8927e3006f8314 Author: Ben Gamari Date: Tue Jun 27 21:39:36 2017 -0400 Don't use deleteDir I suspect it is the reason that builds have been mysteriously failing despite all steps succeeding. >--------------------------------------------------------------- c1aabd5dbd902ed848b7c00c5e8927e3006f8314 Jenkinsfile | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index fee5743..7f366d5 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -229,12 +229,12 @@ def withTempDir(String name, Closure f) { rm -Rf ${name} || true mkdir ${name} """ - dir(name) { - try { + try { + dir(name) { f() - } finally { - deleteDir() } + } finally { + sh "rm -Rf ${name}" } } @@ -260,12 +260,12 @@ def withGhcBinDist(String targetTriple, Closure f) { def metadata = readJSON file: "bindist.json" sh "tar -xf ${metadata.tarName}" sh "tar -xf ghc-testsuite.tar.xz" - dir(metadata.dirName) { - try { + try { + dir(metadata.dirName) { f() - } finally { - deleteDir() } + } finally { + sh "rm -R ${metadata.dirName}" } } } From git at git.haskell.org Thu Jul 27 20:50:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:55 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: More debugging (df4de7f) Message-ID: <20170727205055.BB0C93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/df4de7f8b576b6dbfbf09d84a35e65da366c4bba/ghc >--------------------------------------------------------------- commit df4de7f8b576b6dbfbf09d84a35e65da366c4bba Author: Ben Gamari Date: Sat Jun 3 17:02:01 2017 -0400 More debugging >--------------------------------------------------------------- df4de7f8b576b6dbfbf09d84a35e65da366c4bba Jenkinsfile | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 151bc7b..b40186c 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -162,8 +162,9 @@ def buildGhc(params) { json.put('dirName', getMakeValue(makeCmd, 'BIN_DIST_NAME')) json.put('ghcVersion', getMakeValue(makeCmd, 'ProjectVersion')) json.put('targetPlatform', getMakeValue(makeCmd, 'TARGETPLATFORM')) + echo "${json}" + echo json.toString() writeJSON(file: 'bindist.json', json: json) - 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}" @@ -177,9 +178,9 @@ 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' + echo "${metadata}" sh "tar -xf ${metadata.tarName}" - dir("${metadata.bindistName}") { + dir("${metadata.dirName}") { try { f } finally { From git at git.haskell.org Thu Jul 27 20:50:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:50:58 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarball names (c86cec4) Message-ID: <20170727205058.7682D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c86cec4b6731cce5a1834c1940bd266265f3e8c1/ghc >--------------------------------------------------------------- commit c86cec4b6731cce5a1834c1940bd266265f3e8c1 Author: Ben Gamari Date: Sun Jun 4 10:34:37 2017 -0400 Fix tarball names >--------------------------------------------------------------- c86cec4b6731cce5a1834c1940bd266265f3e8c1 Jenkinsfile | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 3b31238..d2f39f3 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -35,10 +35,11 @@ stage("Build source distribution") { """ } stage("Build tarballs") { + def version = getMakeValue('make', 'ProjectVersion') sh "make sdist" - sh "mv sdistprep/ghc-*.tar.xz ghc-src.tar.xz" - sh "mv sdistprep/ghc-*-testsuite.tar.xz ghc-testsuite.tar.xz" - sh "mv sdistprep/ghc-*-windows-extra-src-*.tar.xz ghc-win32-tarballs.tar.xz" + sh "mv sdistprep/ghc-${version}-src.tar.xz ghc-src.tar.xz" + sh "mv sdistprep/ghc-${version}-testsuite.tar.xz ghc-testsuite.tar.xz" + sh "mv sdistprep/ghc-${version}-windows-extra-src.tar.xz ghc-win32-tarballs.tar.xz" stash(name: 'source-dist', includes: 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz') stash(name: 'testsuite-dist', includes: 'ghc-testsuite.tar.xz') } @@ -194,7 +195,7 @@ def buildGhc(params) { } def getMakeValue(String makeCmd, String value) { - return sh(script: "${makeCmd} -s echo VALUE=${value}", returnStdout: true) + return sh(script: "${makeCmd} -s echo! VALUE=${value}", returnStdout: true) } def withTempDir(String name, Closure f) { From git at git.haskell.org Thu Jul 27 20:51:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:01 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: debug win32 (6d1ec37) Message-ID: <20170727205101.2F33C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/6d1ec37ed8cfa09de1c27a9e0e3e1e77318ca359/ghc >--------------------------------------------------------------- commit 6d1ec37ed8cfa09de1c27a9e0e3e1e77318ca359 Author: Ben Gamari Date: Sat Jun 17 23:34:18 2017 -0400 debug win32 >--------------------------------------------------------------- 6d1ec37ed8cfa09de1c27a9e0e3e1e77318ca359 Jenkinsfile | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index b754745..451a3a5 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -155,6 +155,9 @@ def buildGhc(params) { withGhcSrcDist() { stage('Configure') { + echo 'echo $PATH' + sh "which ghc" + def speed = 'NORMAL' if (params.nightly) { speed = 'SLOW' @@ -271,8 +274,6 @@ def testGhc(params) { withGhcBinDist(targetTriple) { stage('Configure') { - echo 'echo $PATH' - sh "which ghc" if (isUnix()) { sh "./configure --prefix=\"${instDir}\"" sh "${makeCmd} install" From git at git.haskell.org Thu Jul 27 20:51:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:03 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Show location of stage0 compiler (2851b36) Message-ID: <20170727205103.DD91F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2851b36f11a5281b4628eea7623fbebaec020866/ghc >--------------------------------------------------------------- commit 2851b36f11a5281b4628eea7623fbebaec020866 Author: Ben Gamari Date: Tue Jun 13 16:10:23 2017 -0400 Show location of stage0 compiler >--------------------------------------------------------------- 2851b36f11a5281b4628eea7623fbebaec020866 Jenkinsfile | 1 + 1 file changed, 1 insertion(+) diff --git a/Jenkinsfile b/Jenkinsfile index 486e975..1c6fa39 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -272,6 +272,7 @@ def testGhc(params) { withGhcBinDist(targetTriple) { stage('Configure') { + sh "which ghc" sh "./configure --prefix=\"`pwd`/${instDir}\"" sh "${makeCmd} install" } From git at git.haskell.org Thu Jul 27 20:51:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:06 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix testGhc (3873a55) Message-ID: <20170727205106.9DC213A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/3873a559d227b9c431133b8fd2e218516ed85879/ghc >--------------------------------------------------------------- commit 3873a559d227b9c431133b8fd2e218516ed85879 Author: Ben Gamari Date: Tue Jun 27 23:01:00 2017 -0400 Fix testGhc >--------------------------------------------------------------- 3873a559d227b9c431133b8fd2e218516ed85879 Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 7f366d5..c135b9d 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -273,9 +273,9 @@ def withGhcBinDist(String targetTriple, Closure f) { def testGhc(params) { String targetTriple = params?.targetTriple // See Note [Spaces in TEST_HC] - String testGhc="${instDir}/bin/ghc" String makeCmd = params?.makeCmd ?: 'make' String instDir="${pwd()}/bindisttest/install dir" + String testGhc="${instDir}/bin/ghc" withGhcBinDist(targetTriple) { stage('Configure') { From git at git.haskell.org Thu Jul 27 20:51:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:09 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Preserve file attributes when copying bindist into place (b03fcce) Message-ID: <20170727205109.5878B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/b03fcce7cf64ebf4d0a6874cbbab3c0d3a7c5474/ghc >--------------------------------------------------------------- commit b03fcce7cf64ebf4d0a6874cbbab3c0d3a7c5474 Author: Ben Gamari Date: Sat Jul 8 15:20:39 2017 -0400 Preserve file attributes when copying bindist into place >--------------------------------------------------------------- b03fcce7cf64ebf4d0a6874cbbab3c0d3a7c5474 Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index ab92bfe..ec9e1d9 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -284,7 +284,7 @@ def testGhc(params) { sh "${makeCmd} install" } else { sh "mkdir -p \"${instDir}\"" - sh "cp -R * \"${instDir}\"" + sh "cp -a * \"${instDir}\"" } } From git at git.haskell.org Thu Jul 27 20:51:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:12 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarName (2da8f61) Message-ID: <20170727205112.1C1C33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2da8f619de5540634eab6afd55d7cfd46b54f4c6/ghc >--------------------------------------------------------------- commit 2da8f619de5540634eab6afd55d7cfd46b54f4c6 Author: Ben Gamari Date: Sat Jun 3 21:33:12 2017 -0400 Fix tarName >--------------------------------------------------------------- 2da8f619de5540634eab6afd55d7cfd46b54f4c6 Jenkinsfile | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index b40186c..830afd1 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -156,14 +156,13 @@ def buildGhc(params) { sh "${makeCmd} binary-dist" def json = new JSONObject() def tarPath = getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') - def tarName = sh "basename ${tarPath}" + def tarName = sh(script: "basename ${tarPath}", returnStdout: true) 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')) echo "${json}" - echo json.toString() writeJSON(file: 'bindist.json', json: json) // 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 Thu Jul 27 20:51:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:14 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Handle documentation (9e36489) Message-ID: <20170727205114.C98B63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9e36489a72e1820750375274c54f1e53284eb457/ghc >--------------------------------------------------------------- commit 9e36489a72e1820750375274c54f1e53284eb457 Author: Ben Gamari Date: Tue May 30 01:46:06 2017 -0400 Handle documentation >--------------------------------------------------------------- 9e36489a72e1820750375274c54f1e53284eb457 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 Thu Jul 27 20:51:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:17 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix testsuite (9c5f6a8) Message-ID: <20170727205117.810543A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9c5f6a8fbaadf07d50dac2e2793a91e47f5b0314/ghc >--------------------------------------------------------------- commit 9c5f6a8fbaadf07d50dac2e2793a91e47f5b0314 Author: Ben Gamari Date: Tue May 30 12:11:16 2017 -0400 Fix testsuite >--------------------------------------------------------------- 9c5f6a8fbaadf07d50dac2e2793a91e47f5b0314 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 Thu Jul 27 20:51:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:20 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Ensure HOME is expanded (a57c1a1) Message-ID: <20170727205120.405CB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a57c1a1df78adae789e694f4ec4182382f26e478/ghc >--------------------------------------------------------------- commit a57c1a1df78adae789e694f4ec4182382f26e478 Author: Ben Gamari Date: Sun Jun 18 16:35:12 2017 -0400 Ensure HOME is expanded >--------------------------------------------------------------- a57c1a1df78adae789e694f4ec4182382f26e478 Jenkinsfile | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index d559f06..9aac44f 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -111,14 +111,15 @@ def withMingw(String msystem, Closure f) { // Derived from msys2's /etc/msystem def msysRoot = 'C:\\msys64' String carch, prefix, ghcPath + home = sh(script: 'echo $HOME', returnStdout: true) if (msystem == 'MINGW32') { prefix = "${msysRoot}\\mingw32" carch = 'i686' - ghcPath = '$HOME/ghc-8.0.1-i386/bin' + ghcPath = "${home}/ghc-8.0.1-i386/bin" } else if (msystem == 'MINGW64') { prefix = "${msysRoot}\\mingw64" carch = 'x86_64' - ghcPath = '$HOME/ghc-8.0.2-x86_64/bin' + ghcPath = "${home}/ghc-8.0.2-x86_64/bin" } else { fail } From git at git.haskell.org Thu Jul 27 20:51:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:22 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Actually call closure (c12c44e) Message-ID: <20170727205122.F1FEC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c12c44ed923a32a636e39c481e2b42d31f48be65/ghc >--------------------------------------------------------------- commit c12c44ed923a32a636e39c481e2b42d31f48be65 Author: Ben Gamari Date: Sun Jun 4 01:02:20 2017 -0400 Actually call closure >--------------------------------------------------------------- c12c44ed923a32a636e39c481e2b42d31f48be65 Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 830afd1..fa710c3 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -181,7 +181,7 @@ def withGhcBinDist(String targetTriple, Closure f) { sh "tar -xf ${metadata.tarName}" dir("${metadata.dirName}") { try { - f + f() } finally { deleteDir() } From git at git.haskell.org Thu Jul 27 20:51:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:25 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: debugging (6e4c30c) Message-ID: <20170727205125.AE29D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/6e4c30cf80ae34498bf5de8b164bf6a09191964c/ghc >--------------------------------------------------------------- commit 6e4c30cf80ae34498bf5de8b164bf6a09191964c Author: Ben Gamari Date: Fri Jun 16 14:31:43 2017 -0400 debugging >--------------------------------------------------------------- 6e4c30cf80ae34498bf5de8b164bf6a09191964c Jenkinsfile | 1 + 1 file changed, 1 insertion(+) diff --git a/Jenkinsfile b/Jenkinsfile index 25ad7f1..179421e 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -271,6 +271,7 @@ def testGhc(params) { withGhcBinDist(targetTriple) { stage('Configure') { + echo 'echo $PATH' sh "which ghc" sh "./configure --prefix=\"`pwd`/${instDir}\"" sh "${makeCmd} install" From git at git.haskell.org Thu Jul 27 20:51:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:28 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix binding name (49e41a9) Message-ID: <20170727205128.68FB53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/49e41a9c84ff1a871ea4d273cc3c2b73c846f35a/ghc >--------------------------------------------------------------- commit 49e41a9c84ff1a871ea4d273cc3c2b73c846f35a Author: Ben Gamari Date: Mon Jun 12 22:25:11 2017 -0400 Fix binding name >--------------------------------------------------------------- 49e41a9c84ff1a871ea4d273cc3c2b73c846f35a Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 9f87698..24810c5 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -272,7 +272,7 @@ def testGhc(params) { withGhcBinDist(targetTriple) { stage('Configure') { - sh "./configure --prefix=\"`pwd`/${inst_dir}\"" + sh "./configure --prefix=\"`pwd`/${instDir}\"" sh "${makeCmd} install" } From git at git.haskell.org Thu Jul 27 20:51:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:31 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix source directory name (aabe200) Message-ID: <20170727205131.1F02D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/aabe2006c142492441b336430b344f57e8eee566/ghc >--------------------------------------------------------------- commit aabe2006c142492441b336430b344f57e8eee566 Author: Ben Gamari Date: Sun Jun 4 11:06:15 2017 -0400 Fix source directory name >--------------------------------------------------------------- aabe2006c142492441b336430b344f57e8eee566 Jenkinsfile | 11 +++++++++-- 1 file changed, 9 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index b709774..59daa63 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -40,7 +40,12 @@ stage("Build source distribution") { sh "mv sdistprep/ghc-${version}-src.tar.xz ghc-src.tar.xz" sh "mv sdistprep/ghc-${version}-testsuite.tar.xz ghc-testsuite.tar.xz" sh "mv sdistprep/ghc-${version}-windows-extra-src.tar.xz ghc-win32-tarballs.tar.xz" - stash(name: 'source-dist', includes: 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz') + + def json = new JSONObject() + json.put('dirName', "ghc-${version}") + writeJSON(file: 'src-dist.json', json: json) + + stash(name: 'source-dist', includes: 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz,src-dist.json') stash(name: 'testsuite-dist', includes: 'ghc-testsuite.tar.xz') } } @@ -216,7 +221,9 @@ def withGhcSrcDist(Closure f) { sh 'tar -xf ghc-src.tar.xz' sh 'tar -xf ghc-win32-tarballs.tar.xz' } - dir('ghc-*') { + + def metadata = readJSON file: 'src-dist.json' + dir(metadata.dirName) { f() } } From git at git.haskell.org Thu Jul 27 20:51:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:33 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Hopefully fix Windows (4f30ea1) Message-ID: <20170727205133.D3BEF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/4f30ea1f0271948a80cc67e4feff955c06fb3fab/ghc >--------------------------------------------------------------- commit 4f30ea1f0271948a80cc67e4feff955c06fb3fab Author: Ben Gamari Date: Mon May 29 22:33:46 2017 -0400 Hopefully fix Windows >--------------------------------------------------------------- 4f30ea1f0271948a80cc67e4feff955c06fb3fab 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 Thu Jul 27 20:51:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:36 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: bindist: Compress with threaded xz by default (bfb90f3) Message-ID: <20170727205136.90E993A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/bfb90f3657aae50af543536e2da5a7a438f2407e/ghc >--------------------------------------------------------------- commit bfb90f3657aae50af543536e2da5a7a438f2407e Author: Ben Gamari Date: Sun Jun 4 12:19:13 2017 -0400 bindist: Compress with threaded xz by default >--------------------------------------------------------------- bfb90f3657aae50af543536e2da5a7a438f2407e mk/config.mk.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index 2e920ca..45e5587 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -795,7 +795,7 @@ else ifeq "$(TAR_COMP)" "gzip" TAR_COMP_CMD = $(GZIP_CMD) TAR_COMP_EXT = gz else ifeq "$(TAR_COMP)" "xz" -TAR_COMP_CMD = $(XZ_CMD) +TAR_COMP_CMD = $(XZ_CMD) --threads=0 TAR_COMP_EXT = xz else $(error $$(TAR_COMP) set to unknown value "$(TAR_COMP)" (supported: "bzip2", "gzip", "xz")) From git at git.haskell.org Thu Jul 27 20:51:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:39 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: A bit more paranoia around directory deletion (d78b4cc) Message-ID: <20170727205139.4A5AE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d78b4ccb4daf27cc67749187be5e7f45b601ce00/ghc >--------------------------------------------------------------- commit d78b4ccb4daf27cc67749187be5e7f45b601ce00 Author: Ben Gamari Date: Sun Jun 4 10:51:43 2017 -0400 A bit more paranoia around directory deletion It seems that the finally block never executes in some cases. Arg. >--------------------------------------------------------------- d78b4ccb4daf27cc67749187be5e7f45b601ce00 Jenkinsfile | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 6615265..b7c9db5 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -196,7 +196,10 @@ def getMakeValue(String makeCmd, String value) { } def withTempDir(String name, Closure f) { - sh "mkdir ${name}" + sh """ + rm -Rf ${name} || true + mkdir ${name} + """ dir(name) { try { f() From git at git.haskell.org Thu Jul 27 20:51:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:42 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Configure bindist (8944cb0) Message-ID: <20170727205142.041563A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/8944cb0c3c8c82c09b259c709689ee9b9cddfff4/ghc >--------------------------------------------------------------- commit 8944cb0c3c8c82c09b259c709689ee9b9cddfff4 Author: Ben Gamari Date: Sun Jun 4 12:32:40 2017 -0400 Configure bindist >--------------------------------------------------------------- 8944cb0c3c8c82c09b259c709689ee9b9cddfff4 Jenkinsfile | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/Jenkinsfile b/Jenkinsfile index db32f78..c369979 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -253,6 +253,10 @@ def testGhc(params) { boolean runNofib = params?.runNofib withGhcBinDist(targetTriple) { + stage('Configure') { + sh './configure' + } + stage('Install testsuite dependencies') { if (params.nightly) { def pkgs = ['mtl', 'parallel', 'parsec', 'primitive', 'QuickCheck', From git at git.haskell.org Thu Jul 27 20:51:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:44 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (8337e9b) Message-ID: <20170727205144.B1E063A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/8337e9bd4a4889a7aef7523d47dba2b26d5829b9/ghc >--------------------------------------------------------------- commit 8337e9bd4a4889a7aef7523d47dba2b26d5829b9 Author: Ben Gamari Date: Sun Jun 4 11:32:08 2017 -0400 Debug >--------------------------------------------------------------- 8337e9bd4a4889a7aef7523d47dba2b26d5829b9 Jenkinsfile | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index bad87bf..1f31e29 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -42,7 +42,8 @@ stage("Build source distribution") { sh "mv sdistprep/ghc-${version}-windows-extra-src.tar.xz ghc-win32-tarballs.tar.xz" def json = new JSONObject() - json.put('dirName', "ghc-${version}") + json.put('dirName', "ghc-${version}" as String) + echo "${json}" writeJSON(file: 'src-dist.json', json: json) stash(name: 'source-dist', includes: 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz,src-dist.json') From git at git.haskell.org Thu Jul 27 20:51:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:47 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix missing binding (c3f1725) Message-ID: <20170727205147.73D8C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c3f1725135cd549d7f81422cfdc59052d173ce35/ghc >--------------------------------------------------------------- commit c3f1725135cd549d7f81422cfdc59052d173ce35 Author: Ben Gamari Date: Wed May 31 11:36:00 2017 -0400 Fix missing binding >--------------------------------------------------------------- c3f1725135cd549d7f81422cfdc59052d173ce35 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 Thu Jul 27 20:51:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:50 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarball generation (a1a0c88) Message-ID: <20170727205150.2CF193A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a1a0c88a4cabd5b2d14e0dcbbcdb0d42e2925f2b/ghc >--------------------------------------------------------------- commit a1a0c88a4cabd5b2d14e0dcbbcdb0d42e2925f2b Author: Ben Gamari Date: Tue May 30 10:43:09 2017 -0400 Fix tarball generation >--------------------------------------------------------------- a1a0c88a4cabd5b2d14e0dcbbcdb0d42e2925f2b 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 Thu Jul 27 20:51:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:52 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rework handling of nofib (29dc4be) Message-ID: <20170727205152.DD9393A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/29dc4be06cca2a223539dcdd6ede2fc18c092c68/ghc >--------------------------------------------------------------- commit 29dc4be06cca2a223539dcdd6ede2fc18c092c68 Author: Ben Gamari Date: Mon Jun 5 13:32:37 2017 -0400 Rework handling of nofib Given that we want the measurements to be stable it makes sense to do these on a separate, quiet machine. >--------------------------------------------------------------- 29dc4be06cca2a223539dcdd6ede2fc18c092c68 Jenkinsfile | 32 +++++++++++++++++++++----------- 1 file changed, 21 insertions(+), 11 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 6fc89ae..adf8058 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -96,6 +96,13 @@ parallel ( */ ) +if (params.runNofib) { + node(label: 'linux && amd64 && perf') { + nofib(targetTriple: 'x86_64-linux-gnu') + } +} + + def withMingw(String msystem, Closure f) { // Derived from msys2's /etc/msystem def msysRoot = 'C:\\msys64' @@ -252,7 +259,6 @@ def withGhcBinDist(String targetTriple, Closure f) { def testGhc(params) { String targetTriple = params?.targetTriple String makeCmd = params?.makeCmd ?: 'make' - boolean runNofib = params?.runNofib withGhcBinDist(targetTriple) { stage('Configure') { @@ -276,18 +282,22 @@ def testGhc(params) { sh "${makeCmd} -Ctestsuite/tests stage=2 LOCAL=0 BINDIST=YES THREADS=${env.THREADS} ${target}" sh "${makeCmd} -Ctestsuite/tests/stage1 stage=1 LOCAL=0 BINDIST=YES THREADS=${env.THREADS} ${target}" } + } +} +def nofib(params) { + String targetTriple = params?.targetTriple + String makeCmd = params?.makeCmd ?: 'make' + withGhcBinDist(targetTriple) { stage('Run nofib') { - if (runNofib) { - installPkgs(['regex-compat']) - sh """ - cd nofib - ${makeCmd} clean - ${makeCmd} boot - ${makeCmd} >../nofib.log 2>&1 - """ - archiveArtifacts artifacts: 'nofib.log' - } + installPkgs(['regex-compat']) + sh """ + cd nofib + ${makeCmd} clean + ${makeCmd} boot + ${makeCmd} >../nofib.log 2>&1 + """ + archiveArtifacts artifacts: 'nofib.log' } } } From git at git.haskell.org Thu Jul 27 20:51:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:55 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix naming of crossCompiling (fae81eb) Message-ID: <20170727205155.9A57A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/fae81ebdf033ba2ba9b2abc0df276ed35a095ff4/ghc >--------------------------------------------------------------- commit fae81ebdf033ba2ba9b2abc0df276ed35a095ff4 Author: Ben Gamari Date: Wed Jul 12 17:01:16 2017 -0400 Fix naming of crossCompiling >--------------------------------------------------------------- fae81ebdf033ba2ba9b2abc0df276ed35a095ff4 Jenkinsfile | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index ec9e1d9..da5021f 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -72,10 +72,10 @@ parallel ( } }, "linux x86-64 -> aarch64 unreg" : { - node(label: 'linux && amd64') {buildAndTestGhc(cross: true, targetTriple: 'aarch64-linux-gnu', unreg: true)} + node(label: 'linux && amd64') {buildAndTestGhc(crossCompiling: true, targetTriple: 'aarch64-linux-gnu', unreg: true)} }, "linux x86-64 -> aarch64" : { - node(label: 'linux && amd64') {buildGhc(cross: true, targetTriple: 'aarch64-linux-gnu')} + node(label: 'linux && amd64') {buildGhc(crossCompiling: true, targetTriple: 'aarch64-linux-gnu')} node(label: 'linux && aarch64') {testGhc(targetTriple: 'aarch64-linux-gnu')} }, "aarch64" : { @@ -153,7 +153,7 @@ def buildAndTestGhc(params) { def buildGhc(params) { String targetTriple = params?.targetTriple - boolean cross = params?.crossTarget ?: false + boolean crossCompiling = params?.crossCompiling ?: false boolean unreg = params?.unreg ?: false boolean disableLargeAddrSpace = params?.disableLargeAddrSpace ?: false String makeCmd = params?.makeCmd ?: 'make' @@ -173,7 +173,7 @@ def buildGhc(params) { ValidateHpc=NO BUILD_DPH=NO """ - if (cross) { + if (crossCompiling) { build_mk += """ # Cross compiling HADDOCK_DOCS=NO @@ -186,7 +186,7 @@ def buildGhc(params) { writeFile(file: 'mk/build.mk', text: build_mk) def configure_opts = [] - if (cross) { + if (crossCompiling) { configure_opts += '--target=${targetTriple}' } if (disableLargeAddrSpace) { From git at git.haskell.org Thu Jul 27 20:51:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:51:58 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Archive source distribution (c494d01) Message-ID: <20170727205158.5F9BD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c494d0157f08d33fe7566ec719797d9bea7000d1/ghc >--------------------------------------------------------------- commit c494d0157f08d33fe7566ec719797d9bea7000d1 Author: Ben Gamari Date: Mon Jun 12 13:34:52 2017 -0400 Archive source distribution >--------------------------------------------------------------- c494d0157f08d33fe7566ec719797d9bea7000d1 Jenkinsfile | 14 ++++++++++---- 1 file changed, 10 insertions(+), 4 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index acaf373..9c2123d 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -48,8 +48,11 @@ stage("Build source distribution") { json.put('commit', resolveCommitSha('HEAD')) writeJSON(file: 'src-dist.json', json: json) - stash(name: 'source-dist', includes: 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz,src-dist.json') + def src_dist_files = 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz,src-dist.json' + stash(name: 'source-dist', includes: src_dist_files) stash(name: 'testsuite-dist', includes: 'ghc-testsuite.tar.xz') + archiveArtifacts artifacts: src_dist_files + archiveArtifacts artifacts: 'ghc-testsuite.tar.xz' } } } @@ -261,11 +264,15 @@ def withGhcBinDist(String targetTriple, Closure f) { def testGhc(params) { String targetTriple = params?.targetTriple + // See Note [Spaces in TEST_HC] + String instDir="bindisttest/install dir" + String testGhc="${instDir}/bin/ghc" String makeCmd = params?.makeCmd ?: 'make' withGhcBinDist(targetTriple) { stage('Configure') { - sh './configure' + sh "./configure --prefix=\"`pwd`/${inst_dir}\"" + sh "${makeCmd} install" } stage('Install testsuite dependencies') { @@ -282,8 +289,7 @@ def testGhc(params) { if (params.nightly) { target = 'slowtest' } - sh "${makeCmd} -Ctestsuite/tests stage=2 LOCAL=0 BINDIST=YES THREADS=${env.THREADS} ${target}" - sh "${makeCmd} -Ctestsuite/tests/stage1 stage=1 LOCAL=0 BINDIST=YES THREADS=${env.THREADS} ${target}" + sh "${makeCmd} -Ctestsuite/tests LOCAL=0 BINDIST=YES THREADS=${env.THREADS} TEST_HC=\"`pwd`/${testGhc}\" ${target}" } } } From git at git.haskell.org Thu Jul 27 20:52:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:52:01 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Trim whitespace from git output (3a51668) Message-ID: <20170727205201.21C7D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/3a51668d4ee91f24f4f6ef4af862239a4a3ec2b4/ghc >--------------------------------------------------------------- commit 3a51668d4ee91f24f4f6ef4af862239a4a3ec2b4 Author: Ben Gamari Date: Sun Jun 4 11:00:28 2017 -0400 Trim whitespace from git output >--------------------------------------------------------------- 3a51668d4ee91f24f4f6ef4af862239a4a3ec2b4 Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 410a86d..b709774 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -279,7 +279,7 @@ def testGhc(params) { } def resolveCommitSha(String ref) { - return sh(script: "git rev-parse ${ref}", returnStdout: true) + return sh(script: "git rev-parse ${ref}", returnStdout: true).trim() } // Push update to ghc.readthedocs.org. From git at git.haskell.org Thu Jul 27 20:52:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:52:03 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Build from source distribution (3c0ab93) Message-ID: <20170727205203.D460D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/3c0ab93098f645312240385c2f540fe719bfab1e/ghc >--------------------------------------------------------------- commit 3c0ab93098f645312240385c2f540fe719bfab1e Author: Ben Gamari Date: Mon May 29 13:55:58 2017 -0400 Build from source distribution >--------------------------------------------------------------- 3c0ab93098f645312240385c2f540fe719bfab1e Jenkinsfile | 181 ++++++++++++++++++++++++++++++++++++++---------------------- 1 file changed, 116 insertions(+), 65 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index fa710c3..3b31238 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -18,6 +18,33 @@ properties( ]) ]) + +stage("Build source distribution") { + node(label: 'linux') { + stage("Checking out tree") { + checkout scm + sh """ + git submodule update --init --recursive + mk/get-win32-tarballs.sh fetch all + """ + } + stage("Configuring tree") { + sh """ + ./boot + ./configure + """ + } + stage("Build tarballs") { + sh "make sdist" + sh "mv sdistprep/ghc-*.tar.xz ghc-src.tar.xz" + sh "mv sdistprep/ghc-*-testsuite.tar.xz ghc-testsuite.tar.xz" + sh "mv sdistprep/ghc-*-windows-extra-src-*.tar.xz ghc-win32-tarballs.tar.xz" + stash(name: 'source-dist', includes: 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz') + stash(name: 'testsuite-dist', includes: 'ghc-testsuite.tar.xz') + } + } +} + parallel ( "linux x86-64" : { node(label: 'linux && amd64') { @@ -103,70 +130,66 @@ def buildGhc(params) { boolean disableLargeAddrSpace = params?.disableLargeAddrSpace ?: false String makeCmd = params?.makeCmd ?: 'make' - stage('Checkout') { - checkout scm - sh "git submodule update --init --recursive" - //sh "${makeCmd} distclean" - } + withGhcSrcDist() { + stage('Configure') { + def speed = 'NORMAL' + if (params.nightly) { + speed = 'SLOW' + } + build_mk = """ + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + """ + if (cross) { + 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) - stage('Configure') { - def speed = 'NORMAL' - if (params.nightly) { - speed = 'SLOW' - } - build_mk = """ - Validating=YES - ValidateSpeed=${speed} - ValidateHpc=NO - BUILD_DPH=NO - """ - if (cross) { - build_mk += """ - # Cross compiling - HADDOCK_DOCS=NO - BUILD_SPHINX_HTML=NO - BUILD_SPHINX_PDF=NO - INTEGER_LIBRARY=integer-simple - WITH_TERMINFO=NO - """ + def configure_opts = [] + if (cross) { + configure_opts += '--target=${targetTriple}' + } + if (disableLargeAddrSpace) { + configure_opts += '--disable-large-address-space' + } + if (unreg) { + configure_opts += '--enable-unregisterised' + } + sh """ + ./boot + ./configure ${configure_opts.join(' ')} + """ } - writeFile(file: 'mk/build.mk', text: build_mk) - def configure_opts = ['--enable-tarballs-autodownload'] - if (cross) { - configure_opts += '--target=${targetTriple}' - } - if (disableLargeAddrSpace) { - configure_opts += '--disable-large-address-space' - } - if (unreg) { - configure_opts += '--enable-unregisterised' + stage('Build') { + sh "${makeCmd} -j${env.THREADS}" } - sh """ - ./boot - ./configure ${configure_opts.join(' ')} - """ - } - - stage('Build') { - sh "${makeCmd} -j${env.THREADS}" - } - stage('Prepare binary distribution') { - sh "${makeCmd} binary-dist" - def json = new JSONObject() - def tarPath = getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') - def tarName = sh(script: "basename ${tarPath}", returnStdout: true) - 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')) - echo "${json}" - writeJSON(file: 'bindist.json', json: 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}" + stage('Prepare binary distribution') { + sh "${makeCmd} binary-dist" + def json = new JSONObject() + def tarPath = getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') + def tarName = sh(script: "basename ${tarPath}", returnStdout: true) + 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')) + echo "${json}" + writeJSON(file: 'bindist.json', json: 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}" + } } } @@ -174,12 +197,9 @@ 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 metadata = readJSON file: "bindist.json" - echo "${metadata}" - sh "tar -xf ${metadata.tarName}" - dir("${metadata.dirName}") { +def withTempDir(String name, Closure f) { + sh "mkdir ${name}" + dir(name) { try { f() } finally { @@ -188,6 +208,37 @@ def withGhcBinDist(String targetTriple, Closure f) { } } +def withGhcSrcDist(Closure f) { + withTempDir('src-dist') { + stage('Unpack source distribution') { + unstash(name: "source-dist") + sh 'tar -xf ghc-src.tar.xz' + sh 'tar -xf ghc-win32-tarballs.tar.xz' + } + dir('ghc-*') { + f() + } + } +} + +def withGhcBinDist(String targetTriple, Closure f) { + withTempDir('bin-dist') { + unstash "bindist-${targetTriple}" + unstash "testsuite-dist" + def metadata = readJSON file: "bindist.json" + echo "${metadata}" + sh "tar -xf ${metadata.tarName}" + sh "tar -xf ghc-testsuite.tar.xz" + dir("${metadata.dirName}") { + try { + f() + } finally { + deleteDir() + } + } + } +} + def testGhc(params) { String targetTriple = params?.targetTriple String makeCmd = params?.makeCmd ?: 'make' From git at git.haskell.org Thu Jul 27 20:52:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:52:06 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rip out debug output (6646643) Message-ID: <20170727205206.8C5153A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/66466432a27938f6a4f6018e11ef0550bccf645f/ghc >--------------------------------------------------------------- commit 66466432a27938f6a4f6018e11ef0550bccf645f Author: Ben Gamari Date: Sun Jun 4 11:36:21 2017 -0400 Rip out debug output >--------------------------------------------------------------- 66466432a27938f6a4f6018e11ef0550bccf645f Jenkinsfile | 4 ---- 1 file changed, 4 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 1f31e29..db32f78 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -43,7 +43,6 @@ stage("Build source distribution") { def json = new JSONObject() json.put('dirName', "ghc-${version}" as String) - echo "${json}" writeJSON(file: 'src-dist.json', json: json) stash(name: 'source-dist', includes: 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz,src-dist.json') @@ -225,8 +224,6 @@ def withGhcSrcDist(Closure f) { def metadata = readJSON file: 'src-dist.json' sh "cat src-dist.json" - echo "${metadata}" - sh "echo ${metadata.dirName}; ls ${metadata.dirName}" dir(metadata.dirName) { f() } @@ -238,7 +235,6 @@ def withGhcBinDist(String targetTriple, Closure f) { unstash "bindist-${targetTriple}" unstash "testsuite-dist" def metadata = readJSON file: "bindist.json" - echo "${metadata}" sh "tar -xf ${metadata.tarName}" sh "tar -xf ghc-testsuite.tar.xz" dir(metadata.dirName) { From git at git.haskell.org Thu Jul 27 20:52:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:52:09 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Clean (d290e6f) Message-ID: <20170727205209.4A1A23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d290e6f05bd1595a820dc65bf23c65e4da2d8cec/ghc >--------------------------------------------------------------- commit d290e6f05bd1595a820dc65bf23c65e4da2d8cec Author: Ben Gamari Date: Tue May 30 00:29:29 2017 -0400 Clean >--------------------------------------------------------------- d290e6f05bd1595a820dc65bf23c65e4da2d8cec 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 Thu Jul 27 20:52:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Jul 2017 20:52:13 +0000 (UTC) Subject: [commit: ghc] wip/jenkins's head updated: Fix naming of crossCompiling (fae81eb) Message-ID: <20170727205213.81A363A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/jenkins' now includes: 559a0c5 Fix out-of-date comments in TyCoRep 8573100 Look through type synonyms in existential contexts when deriving Functor df32880 Typofix in Data.Type.Equality comments b9f9670 rts: Ensure that new capability count is > 0 e12ea39 rts: A bit of cleanup around the eventlog 04ca036 testsuite: Add testcase for #13822 ee9232524 Add fixity declaration for :~~: 23f47b1 Add T9630 bea18a0 Fix GCC 7 warning in the RTS 990928f Don't expose fingerprints from Type.Reflection 271e0f0 Add test cases for #13821 a9b62a3 configure: Look for objdump on OpenBSD and AIX 6a2264d cmm/CmmLayoutStack: avoid generating unnecessary reloads 564a31f Reword documentation region overlap documentation for copying mutable arrays 986deaa Add missing -Wdeprecations flag to the users guide 5c93df9 Improve comments on AbsBinds b1fa386 Fix note reference [ci skip] 6dd1257 UNREG: use __builtin___clear_cache where available 88263f9 base: Export Fingerprint accessors from Type.Reflection.Unsafe c85cd9b Show only the number of modules in ghci c8370a8 change filtering of variables in extract_hs_tv_bndrs (fixes #13782) c6fe403 Revert "UNREG: use __builtin___clear_cache where available" d1d3e98 rts: Suppress unused gcc_clear_cache warning 76769bd Revert "rts: Suppress unused gcc_clear_cache warning" a9bf7d4 Fix typo 34b7f63 UNREG: use __builtin___clear_cache where available 84cf095 compiler: Eliminate pprTrace in SPT entry addition codepath e13edee testsuite: Fix cabal01 test 398a444 Add fixity declaration for Data.List.NonEmpty.!! 3c4537e Fix pretty-printing of zero-argument lambda expressions 9077120 Use actual universal tvs in check for naughty record selectors 42eee6e Hoopl: remove dependency on Hoopl package faefa7e documentation: fix trac issue #12978 a48464a users guide: Rephrasing 904255e DWARF: Use .short to render half-machine-words 4bd4f56 rts: Always collect stats 86abe0e users-guide/debug-info: Fix incorrect DWARF tags b8f8736 base/inputReady: Whitespace cleanup 914962c Update docs to reflect changes to DeriveDataTypeable 9ef909d Allow bytecode interpreter to make unsafe foreign calls 12a3c39 testsuite: Add broken test for #13871 1346525 typecheck: Consider types containing coercions non-Typeable 1e47126 rts: Clarify whitehole logic in threadPaused 6567c81 Treat banged bindings as FunBinds b070858 Make module membership on ModuleGraph faster 22b917e Revert "Make module membership on ModuleGraph faster" 4bdac33 Fix the in-scope set in TcHsType.instantiateTyN c80920d Do zonking in tcLHsKindSig fae672f Fix constraint solving for forall-types 87c5fdb Zap stable unfoldings in worker/wrapper 78c80c2 Typos in comments and manual [ci skip] 3f9422c More typos in comments [ci skip] 7097f94 Remove unneeded import 54ccf0c remove dead function 'tcInstBinders' 3b0e755 Fix lexically-scoped type variables 58c781d Revert "Remove the Windows GCC driver." c2fb6e8 Typos in comments c3f12ec Fix T13701 allocation for Linux 7de2c07 users-guide: Document FFI safety guarantees 6171b0b configure: Check for binutils #17166 007f255 Allow optional instance keyword in associated type family instances 625143f configure: Coerce gcc to use $LD instead of system default 9b514de rts/RetainerProfile: Const-correctness fixes 1ef4156 Prevent ApplicativeDo from applying to strict pattern matches (#13875) 0592318 Fix paper link in MVar docs [ci skip] 544ac0d rename tcInstBinder(s)X to tcInstBinder(s) 84d6831a users-guide: Wibbles in shared libraries discussion 287a405 Allow per-argument documentation on pattern synonym signatures 1a9c3c4 Implement recompilation checking for -fignore-asserts f9c6d53 Tag the FUN before making a PAP (#13767) c3a7862 Fix #13311 by using tcSplitNestedSigmaTys in the right place d55bea1 Fix -fno-code for modules that use -XQuasiQuotes 0c1f905 CmmParse: Emit source notes for assignments 5aee331 Bump array submodule to v0.5.2.0 8f8d756 rts: Fix uninitialised variable uses af403b2 ApplicativeDo: document behaviour with strict patterns (#13875) ef63ff2 configure: Remove --with-curses-includes flag a6f3d1b rts: Fix isByteArrayPinned#'s treatment of large arrays 960918b Add -fuse-ld flag to CFLAGS during configure 0836bfb testsuite: Add testcase for #13615 fd7a7a6 Eagerly blackhole AP_STACKs 9492703 rts/sm/Storage.c: tweak __clear_cache proto for clang 7040660 Revert "rts/sm/Storage.c: tweak __clear_cache proto for clang" 3eeb55e rts/sm/Storage.c: tweak __clear_cache proto for clang 555e5cc rts: Address AP_STACK comment suggestion from Simon 4997177 mkDocs: Don't install *.ps f3979b7 lowercase clang 99adcc8 Typos in comments [ci skip] bd4fdc6 Implement split-sections support for windows. c2303df aclocal.m4: allow arbitrary string in toolchain triplets e1146ed Fix typos in Bag.hs [ci skip] 81377e9 Big-obj support for the Windows runtime linker c506f83 Pretty-printer no longer butchers function arrow fixity 4f69013 testsuite: Decrease T13701 allocations 31ceaba user-guide: Various fixes to FFI section 905dc8b Make ':info Coercible' display an arbitrary string (fixes #12390) 7c9e356 Fix Work Balance computation in RTS stats b0c9f34 Improve Wmissing-home-modules warning under Cabal 6cff2ca Add testcase for T13818 15fcd9a Suppress unused warnings for selectors for some derived classes cb8db9b Sort list of failed tests for easier comparison between runs b8f33bc Always allow -staticlib fe6618b ByteCodeGen: use depth instead of offsets in BCEnv ccb849f users-guide/rel-notes: Describe #13875 fix 81de42c Add Template Haskell support for overloaded labels abda03b Optimize TimerManager ea75124 Fix logic error in GhcMake.enableCodeGenForTH ba46e63 Fix #13948 by being pickier about when to suggest DataKinds 85ac65c Fix #13947 by checking for unbounded names more ef7fd0a Parenthesize infix type names in data declarations in TH printer ec351b8 Add Template Haskell support for overloaded labels a249e93 Remove unnecessarily returned res_ty from rejigConRes d3bdd6c testsuite: Fix T13701 allocations yet again fcd2db1 configure: Ensure that we don't set LD to unusable linker be04c16 StgLint: Don't loop on tycons with runtime rep arguments 20880b5 testsuite: Show stderr output on command failure a0d9169 Fix minor typo 3a163aa Remove redundant import; fix note 4befb41 Mention which -Werror promoted a warning to an error 9b9f978 Use correct section types syntax for architecture 1ee49cb Fix missing escape in macro 60ec8f7 distrib/configure: Fail if we can't detect machine's word size 7ae4a28 [iserv] Fixing the word size for RemotePtr and toWordArray 5743581 testsuite: Update haddock allocations 4700baa testsuite: Again update allocations of T13701 1909985 Fix some excessive spacing in error messages f656fba [skip ci] Temporarily disable split-sections on Windows. 12ae1fa Fix a missing getNewNursery(), and related cleanup 935acb6 Typos in comments and explanation for unusused imports b8fec69 Make module membership on ModuleGraph faster 6ab3c5f Typeable: Always use UTF-8 string unpacking primitive d7b1751 configure: Cleanup ARM COPY bug test artifacts a051b55 testsuite: Ensure that hs_try_putmvar003 terminates c9e4c86 Allow visible type application for [] 1ed41a7 Fix links to SPJ’s papers (fixes #12578) 0b89b2d Add Haddocks for Eq (STRef a) and Eq (IORef a) c940e3b dmdAnal: Ensure that ExnStr flag isn't dropped inappropriately 6e3c901 Fix #13983 by creating a TyConFlavour type, and using it 927e781 typo: -XUndeci[d]ableInstances b066d93 base: Improve docs to clarify when finalizers may not be run cc839c5 Typeable: Ensure that promoted data family instance tycons get bindings a273c73 Spelling fixes eeb141d Demand: Improve comments 8e51bfc Introduce -fcatch-bottoms c9c762d testsuite: Pipe stdin directly to process a85a595 arcconfig: Set project ruleset to use master merge-base by default 194384f Fix busy-wait in SysTools.builderMainLoop fdb6a5b Make IfaceAxiom typechecking lazier. 5469ac8 Interpreter.c: use macros to access/modify Sp bade356 rts: Claim AP_STACK before adjusting Sp 1480080 distrib/configure: Canonicalize triples b2d3ec3 testsuite: Add test for #13916 ccac387 Revert "testsuite: Add test for #13916" 36e8bcb HsPat: Assume that no spliced patterns are irrefutable fefcbfa build system: Ensure there are no duplicate files in bindist list acbbb50 Fix ungrammatical error message cbbf083 fix dllwrap issue. c1d9690 Avoid linear lookup in unload_wkr in the Linker ee1047e Update autoconf scripts 98ab12a distrib/configure: Carry FFI include/lib paths from source distribution fb08252 users-guide: Improve legibility of OverlappingInstances documentation 0ae0f46 Preserve HaskellHaveRTSLinker in bindist 646ec0e Bump a bunch of submodules b8afdaf Update release notes for 8.2.1 fb17cc5 Bump integer-gmp version ecc9e9a ghc-prim: Bump version d4e9721 testsuite: Fix cabal01 for real this time 44b090b users-guide: Standardize and repair all flag references c945195 users-guide: Fix various wibbles 2dff2c7 Fix more documentation wibbles 145f1c7 Remove 8.0.2 release notes file 88f20bd Add a caveat to the GHC.Generics examples about :+: nesting a602b65 users-guides: Fix errant whitespace 0c04d78 users-guide: Cross-reference more flags 58b62d6 users-guide: Eliminate some redundant index entries 3e5d0f1 users-guide: Make it easier to reference haddocks 897366a users-guide: Fix URL of deferred type errors paper 85a295d ghc-prim: Don't allocate a thunk for each unpacked UTF-8 character 8a8cee7 DynFlags: Drop rtsBuildTag field d8051c6 Use libpthread instead of libthr on FreeBSD 8ec7770 testsuite: Add testcase for #13168 2183ac1 Fix import error with -XPackageImports when the module has a duplicate name 58545fd base: Introduce GHC.ByteOrder 104c72b Expose FrontendPluginAction 7d1909a Remove unused language pragma 36b270a Revert "Remove unused language pragma" 6bb32ba Fix #10684 by processing deriving clauses with finer grain 746ab0b Add an Outputable instance for ListMap 75bf11c Fix binder visiblity for default methods 6386fc3 Comments and tc-tracing only f959624 Comments only d31181b Test Trac #14033 362339d Fix note references and some typos d774b4e Fix #13968 by consulting isBuiltInOcc_maybe 4a26415 Remove unneeded import 8e15e3d Improve error messages around kind mismatches. c9667d3 Fix #11400, #11560 by documenting an infelicity. 9a54975 Test #11672 in typecheck/should_fail/T11672. ef39af7 Don't tidy vars when dumping a type bb2a446 Preserve CoVar uniques during pretty printing 79cfb19 Remove old coercion pretty-printer c2417b8 Fix #13819 by refactoring TypeEqOrigin.uo_thing fb75213 Track visibility in TypeEqOrigin 10d13b6 Fix #11963 by checking for more mixed type/kinds ca47186 Document that type holes kill polymorphic recursion 1696dbf Fix #12176 by being a bit more careful instantiating. 4239238 Fix #12369 by being more flexible with data insts 791947d Refactor tcInferApps. 7af0b90 Initialize hs_init with UTF8 encoded arguments on Windows. 9603015 Testing simpler Jenkinsfile 31a94bb Testing 194a78b Add THREADS parameter f777704 Refactoring 4902e35 Move to scripted pipeline a3b22d6 Add nofib, bindist, and aarch64 support defc512 Run jobs in parallel 69b9ddd Debug 318f9da Cross 5f72d8a Checkout 5883de5 More things 9b24deb Kill debugging 9d6d2b3 Unregisterised d622e6d windows cba9eff Refactoring, add Windows, fix cross 4b1e8ac Debug 7f6a9cf Reformat 5008e3e Debug ba8a4c5 Nailed the Windows issue 7ae74fc Rework handling of Windows 5e7868b Fix FreeBSD architecture d89dbdf Parametrize on make command b600c2f Use archiveArtifacts instead of archive 95ae236 Debug dd50a91 Don't run nofib on Windows 90b9ea1 Fix Windows PATHs 7d88f01 Disable large address space on FreeBSD 1f755f4 Try again c8b1b62 Hmm 394772b Disable non-Windows builds 4f30ea1 Hopefully fix Windows 61c7edb Reenable everything else 4206227 Fix configure arguments d290e6f Clean 9390d4d Clean up treatment of tests 9e36489 Handle documentation a1a0c88 Fix tarball generation 8ce55fb Fix documentation 9c5f6a8 Fix testsuite c79a5da Fix test 8deb4cb Be more explicit a58956c Fix JSON serialization c3f1725 Fix missing binding ac4fa1f Debug df4de7f More debugging 2da8f61 Fix tarName c12c44e Actually call closure 3c0ab93 Build from source distribution 9058d44 Introduce echo! make target c86cec4 Fix tarball names a469010 No need to configure d78b4cc A bit more paranoia around directory deletion 6645762 No need to boot 3a51668 Trim whitespace from git output aabe200 Fix source directory name 2aaf460 Debuggging 04ee922 Debug 05e7d5d Try adding type annotation 8337e9b Debug 6646643 Rip out debug output bfb90f3 bindist: Compress with threaded xz by default 8944cb0 Configure bindist ac4da99 Run stage1 tests as well 5bba8db Pass BINDIST to make test 4fe8d91 Use named argument list 29dc4be Rework handling of nofib 2f87ce7 Don't try to record commit of bindist eb9c0b5 Fix windows paths c494d01 Archive source distribution aae4b7d Ensure that carch, prefix, and ghcPath are in scope 7f648a2 Fix quoting of carch 49e41a9 Fix binding name 9c60958 Fix GHC path 2851b36 Show location of stage0 compiler 16e7d1b Kill debug output 6e4c30c debugging 9e9481c Handle testsuite on Windows 6d1ec37 debug win32 ab5ca7d Ugh, sh not echo a57c1a1 Ensure HOME is expanded 698bdd7 No trailing newline e1702b6 Enable win64 again e41f597 Various accumulated fixes c1aabd5 Don't use deleteDir 3873a55 Fix testGhc 9d8e9fa Fix ghc path 9ec5442 Properly quote instDir b03fcce Preserve file attributes when copying bindist into place fae81eb Fix naming of crossCompiling From git at git.haskell.org Fri Jul 28 08:56:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 08:56:28 +0000 (UTC) Subject: [commit: ghc] master: Remove redundant constraint in context (af6d225) Message-ID: <20170728085628.E9A413A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/af6d225ffbeabbaffb68cdee4c377b0e361aad26/ghc >--------------------------------------------------------------- commit af6d225ffbeabbaffb68cdee4c377b0e361aad26 Author: Simon Peyton Jones Date: Thu Jul 27 14:46:38 2017 +0100 Remove redundant constraint in context >--------------------------------------------------------------- af6d225ffbeabbaffb68cdee4c377b0e361aad26 compiler/hsSyn/HsLit.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/hsSyn/HsLit.hs b/compiler/hsSyn/HsLit.hs index 1044f9b..31c7a02 100644 --- a/compiler/hsSyn/HsLit.hs +++ b/compiler/hsSyn/HsLit.hs @@ -101,7 +101,7 @@ data HsOverLit p ol_rebindable :: PostRn p Bool, -- Note [ol_rebindable] ol_witness :: HsExpr p, -- Note [Overloaded literal witnesses] ol_type :: PostTc p Type } -deriving instance (DataId p, DataId p) => Data (HsOverLit p) +deriving instance (DataId p) => Data (HsOverLit p) -- Note [Literal source text] in BasicTypes for SourceText fields in -- the following From git at git.haskell.org Fri Jul 28 08:56:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 08:56:31 +0000 (UTC) Subject: [commit: ghc] master: Fix ASSERT failure in tc269 (b1317a3) Message-ID: <20170728085631.A99503A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b1317a35770b19838c7f6b07e794bfc61419e889/ghc >--------------------------------------------------------------- commit b1317a35770b19838c7f6b07e794bfc61419e889 Author: Simon Peyton Jones Date: Thu Jul 27 14:47:07 2017 +0100 Fix ASSERT failure in tc269 This ASSERT failure (in substTy) was reported in Trac #14024. This patch gets the in-scope set right. (Does not fix tests T13822 or T13594.) >--------------------------------------------------------------- b1317a35770b19838c7f6b07e794bfc61419e889 compiler/typecheck/TcCanonical.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 48c1bec..7b25925 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -24,7 +24,6 @@ import FamInstEnv ( FamInstEnvs ) import FamInst ( tcTopNormaliseNewTypeTF_maybe ) import Var import VarEnv( mkInScopeSet ) -import VarSet import Outputable import DynFlags( DynFlags ) import NameSet @@ -644,8 +643,7 @@ can_eq_nc_forall :: CtEvidence -> EqRel can_eq_nc_forall ev eq_rel s1 s2 | CtWanted { ctev_loc = loc, ctev_dest = orig_dest } <- ev - = do { let free_tvs1 = tyCoVarsOfType s1 - free_tvs2 = tyCoVarsOfType s2 + = do { let free_tvs = tyCoVarsOfTypes [s1,s2] (bndrs1, phi1) = tcSplitForAllTyVarBndrs s1 (bndrs2, phi2) = tcSplitForAllTyVarBndrs s2 ; if not (equalLength bndrs1 bndrs2) @@ -656,7 +654,7 @@ can_eq_nc_forall ev eq_rel s1 s2 ; canEqHardFailure ev s1 s2 } else do { traceTcS "Creating implication for polytype equality" $ ppr ev - ; let empty_subst1 = mkEmptyTCvSubst $ mkInScopeSet free_tvs1 + ; let empty_subst1 = mkEmptyTCvSubst $ mkInScopeSet free_tvs ; (subst1, skol_tvs) <- tcInstSkolTyVarsX empty_subst1 $ binderVars bndrs1 @@ -682,8 +680,7 @@ can_eq_nc_forall ev eq_rel s1 s2 go _ _ _ = panic "cna_eq_nc_forall" -- case (s:ss) [] - empty_subst2 = mkEmptyTCvSubst $ mkInScopeSet $ - free_tvs2 `unionVarSet` closeOverKinds (mkVarSet skol_tvs) + empty_subst2 = mkEmptyTCvSubst (getTCvInScope subst1) ; (implic, _ev_binds, all_co) <- buildImplication skol_info skol_tvs [] $ go skol_tvs empty_subst2 bndrs2 From git at git.haskell.org Fri Jul 28 08:56:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 08:56:35 +0000 (UTC) Subject: [commit: ghc] master: Fix instantiation of pattern synonyms (6b77914) Message-ID: <20170728085635.047263A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6b77914cd37b697354611bcd87897885c1e5b4a6/ghc >--------------------------------------------------------------- commit 6b77914cd37b697354611bcd87897885c1e5b4a6 Author: Simon Peyton Jones Date: Thu Jul 27 14:45:54 2017 +0100 Fix instantiation of pattern synonyms In Check.hs (pattern match ovelap checking) we to figure out the instantiation of a pattern synonym from the type of the pattern. We were doing this utterly wrongly. Trac #13768 demonstrated this bogosity. The fix is easy; and is described in PatSyn.hs Note [Pattern synonym result type] >--------------------------------------------------------------- 6b77914cd37b697354611bcd87897885c1e5b4a6 compiler/basicTypes/PatSyn.hs | 54 +++++++++++++++++++++---- compiler/deSugar/Check.hs | 17 ++++---- testsuite/tests/patsyn/should_compile/T13768.hs | 33 +++++++++++++++ testsuite/tests/patsyn/should_compile/all.T | 1 + 4 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 6b77914cd37b697354611bcd87897885c1e5b4a6 From git at git.haskell.org Fri Jul 28 08:56:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 08:56:38 +0000 (UTC) Subject: [commit: ghc] master: Do not discard insolubles in implications (452755d) Message-ID: <20170728085638.9F9A63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/452755de717fad5d8fbfc6330cb42a3335c8912d/ghc >--------------------------------------------------------------- commit 452755de717fad5d8fbfc6330cb42a3335c8912d Author: Simon Peyton Jones Date: Thu Jul 27 14:52:38 2017 +0100 Do not discard insolubles in implications Trac #14000 showed up two errors * In TcRnTypes.dropInsolubles we dropped all implications, which might contain the very insolubles we wanted to keep. This was an outright error, and is why the out-of-scope error was actually lost altogether in Trac #14000 * In TcSimplify.simplifyInfer, if there are definite (insoluble) errors, it's better to suppress the following ambiguity test, because the type may be bogus anyway. See TcSimplify Note [Quantification with errors]. This fix seems a bit clunky, but it'll do for now. >--------------------------------------------------------------- 452755de717fad5d8fbfc6330cb42a3335c8912d compiler/typecheck/TcBinds.hs | 22 ++-- compiler/typecheck/TcExpr.hs | 2 +- compiler/typecheck/TcPatSyn.hs | 4 +- compiler/typecheck/TcRnDriver.hs | 6 +- compiler/typecheck/TcRnTypes.hs | 8 +- compiler/typecheck/TcSimplify.hs | 124 ++++++++++++++------- testsuite/tests/parser/should_fail/T7848.hs | 2 +- testsuite/tests/parser/should_fail/T7848.stderr | 13 +-- testsuite/tests/th/T5358.stderr | 20 ++++ testsuite/tests/typecheck/should_fail/T14000.hs | 8 ++ .../tests/typecheck/should_fail/T14000.stderr | 2 + testsuite/tests/typecheck/should_fail/T8142.stderr | 26 +++-- testsuite/tests/typecheck/should_fail/all.T | 1 + 13 files changed, 161 insertions(+), 77 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 452755de717fad5d8fbfc6330cb42a3335c8912d From git at git.haskell.org Fri Jul 28 08:56:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 08:56:41 +0000 (UTC) Subject: [commit: ghc] master: Add DebugCallStack to piResultTy (ad0037e) Message-ID: <20170728085641.605BA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ad0037ea3ea0eb9e2e693fa10f2171611c4e2217/ghc >--------------------------------------------------------------- commit ad0037ea3ea0eb9e2e693fa10f2171611c4e2217 Author: Simon Peyton Jones Date: Fri Jul 28 09:29:25 2017 +0100 Add DebugCallStack to piResultTy This was provoked by an ASSERT failure when debugging #14038, but it's a godo idea anyway. >--------------------------------------------------------------- ad0037ea3ea0eb9e2e693fa10f2171611c4e2217 compiler/types/Type.hs | 2 +- compiler/types/Type.hs-boot | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index 1c54c44..b81192f 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -943,7 +943,7 @@ funArgTy ty | Just ty' <- coreView ty = funArgTy ty' funArgTy (FunTy arg _res) = arg funArgTy ty = pprPanic "funArgTy" (ppr ty) -piResultTy :: Type -> Type -> Type +piResultTy :: HasDebugCallStack => Type -> Type -> Type piResultTy ty arg = case piResultTy_maybe ty arg of Just res -> res Nothing -> pprPanic "piResultTy" (ppr ty $$ ppr arg) diff --git a/compiler/types/Type.hs-boot b/compiler/types/Type.hs-boot index 41486dd..002db72 100644 --- a/compiler/types/Type.hs-boot +++ b/compiler/types/Type.hs-boot @@ -11,7 +11,7 @@ isCoercionTy :: Type -> Bool mkAppTy :: Type -> Type -> Type mkCastTy :: Type -> Coercion -> Type -piResultTy :: Type -> Type -> Type +piResultTy :: HasDebugCallStack => Type -> Type -> Type typeKind :: Type -> Kind eqType :: Type -> Type -> Bool From git at git.haskell.org Fri Jul 28 15:25:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 15:25:11 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Report JUnit results (ee3c7dc) Message-ID: <20170728152511.9BBD23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ee3c7dcbbbf53c0adc6cca3aab5742ab429daf0e/ghc >--------------------------------------------------------------- commit ee3c7dcbbbf53c0adc6cca3aab5742ab429daf0e Author: Ben Gamari Date: Thu Jul 27 22:44:46 2017 -0400 Report JUnit results >--------------------------------------------------------------- ee3c7dcbbbf53c0adc6cca3aab5742ab429daf0e Jenkinsfile | 1 + 1 file changed, 1 insertion(+) diff --git a/Jenkinsfile b/Jenkinsfile index da5021f..ee6a884 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -303,6 +303,7 @@ def testGhc(params) { target = 'slowtest' } sh "${makeCmd} -Ctestsuite/tests LOCAL=0 BINDIST=YES THREADS=${env.THREADS} TEST_HC=\"${testGhc}\" ${target}" + junit 'testsuite*.xml' } } } From git at git.haskell.org Fri Jul 28 15:52:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 15:52:27 +0000 (UTC) Subject: [commit: ghc] master: Error eagerly after renaming failures in reifyInstances (d618649) Message-ID: <20170728155227.9FFBD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d6186496d414638aa66a677bb4e555dba376ec97/ghc >--------------------------------------------------------------- commit d6186496d414638aa66a677bb4e555dba376ec97 Author: Ryan Scott Date: Fri Jul 28 11:35:22 2017 -0400 Error eagerly after renaming failures in reifyInstances Summary: Previously, if `reifyInstances` failed to discover a `Name` during renaming, it would blindy charge into typechecking, at which point GHC would become very confused at the absence of that `Name` and throw an internal error. A simple workaround is to fail eagerly after renaming errors. Test Plan: make test TEST=T13837 Reviewers: goldfire, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #13837 Differential Revision: https://phabricator.haskell.org/D3793 >--------------------------------------------------------------- d6186496d414638aa66a677bb4e555dba376ec97 compiler/typecheck/TcSplice.hs | 6 +++++- testsuite/tests/th/T13837.hs | 10 ++++++++++ testsuite/tests/th/T13837.stderr | 10 ++++++++++ testsuite/tests/th/all.T | 1 + 4 files changed, 26 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcSplice.hs b/compiler/typecheck/TcSplice.hs index 824227a..266a4df 100644 --- a/compiler/typecheck/TcSplice.hs +++ b/compiler/typecheck/TcSplice.hs @@ -1138,7 +1138,11 @@ reifyInstances th_nm th_tys ; let tv_rdrs = freeKiTyVarsAllVars free_vars -- Rename to HsType Name ; ((tv_names, rn_ty), _fvs) - <- bindLRdrNames tv_rdrs $ \ tv_names -> + <- checkNoErrs $ -- If there are out-of-scope Names here, then we + -- must error before proceeding to typecheck the + -- renamed type, as that will result in GHC + -- internal errors (#13837). + bindLRdrNames tv_rdrs $ \ tv_names -> do { (rn_ty, fvs) <- rnLHsType doc rdr_ty ; return ((tv_names, rn_ty), fvs) } ; (_tvs, ty) diff --git a/testsuite/tests/th/T13837.hs b/testsuite/tests/th/T13837.hs new file mode 100644 index 0000000..3d33341 --- /dev/null +++ b/testsuite/tests/th/T13837.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} +module T13837 where + +import Language.Haskell.TH.Lib +import Language.Haskell.TH.Syntax + +test_local_tyfam_expansion :: String +test_local_tyfam_expansion = + $(do fam_name <- newName "Fam" + stringE . show =<< qReifyInstances fam_name []) diff --git a/testsuite/tests/th/T13837.stderr b/testsuite/tests/th/T13837.stderr new file mode 100644 index 0000000..53700b5 --- /dev/null +++ b/testsuite/tests/th/T13837.stderr @@ -0,0 +1,10 @@ + +T13837.hs:9:5: error: + • The exact Name ‘Fam’ is not in scope + Probable cause: you used a unique Template Haskell name (NameU), + perhaps via newName, but did not bind it + If that's it, then -ddump-splices might be useful + • In the argument of reifyInstances: Fam_0 + In the untyped splice: + $(do fam_name <- newName "Fam" + stringE . show =<< qReifyInstances fam_name []) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index df31162..b52042b 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -389,5 +389,6 @@ test('T13618', normal, compile_and_run, ['-v0']) test('T13642', normal, compile_fail, ['-v0']) test('T13781', normal, compile, ['-v0']) test('T13782', normal, compile, ['']) +test('T13837', normal, compile_fail, ['-v0 -dsuppress-uniques']) test('T13856', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques']) test('T13968', normal, compile_fail, ['-v0']) From git at git.haskell.org Fri Jul 28 15:52:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 15:52:31 +0000 (UTC) Subject: [commit: ghc] master: Merge types and kinds in DsMeta (b3b564f) Message-ID: <20170728155231.2129B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b3b564fbc0ceb06e6a880289935449fda7d33f31/ghc >--------------------------------------------------------------- commit b3b564fbc0ceb06e6a880289935449fda7d33f31 Author: Ryan Scott Date: Fri Jul 28 11:35:37 2017 -0400 Merge types and kinds in DsMeta Summary: Types and kinds are now the same in GHC... well, except in the code that involves Template Haskell, where types and kinds are given separate treatment. This aims to unify that treatment in the `DsMeta` module. The gist of this patch is replacing all uses of `repLKind` with `repLTy`. This is isn't quite as simple as one might imagine, since `repLTy` returns a `Core (Q Type)` (a monadic expression), whereas `repLKind` returns a `Core Kind` (a pure expression). This causes many awkward impedance mismatches. One option would be to change every combinator in `Language.Haskell.TH.Lib` to take `KindQ` as an argument instead of `Kind`. But this would be a breaking change of colossal proportions. Instead, this patch takes a somewhat different approach. This migrates the existing `Language.Haskell.TH.Lib` module to `Language.Haskell.TH.Lib.Internal`, and changes all `Kind`-related combinators in `Language.Haskell.TH.Lib.Internal` to live in `Q`. The new `Language.Haskell.TH.Lib` module then re-exports most of `Language.Haskell.TH.Lib.Internal` with the exception of the `Kind`-related combinators, for which it redefines them to be their current definitions (which don't live in `Q`). This allows us to retain backwards compatibility with previous `template-haskell` releases, but more importantly, it allows GHC to make as many changes to the `Internal` code as it wants for its purposes without fear of disrupting the public API. This solves half of #11785 (the other half being `TcSplice`). Test Plan: ./validate Reviewers: goldfire, austin, bgamari Reviewed By: goldfire Subscribers: rwbarton, thomie GHC Trac Issues: #11785 Differential Revision: https://phabricator.haskell.org/D3751 >--------------------------------------------------------------- b3b564fbc0ceb06e6a880289935449fda7d33f31 compiler/deSugar/DsMeta.hs | 183 ++--- compiler/prelude/THNames.hs | 124 ++- .../template-haskell/Language/Haskell/TH/Lib.hs | 836 ++------------------- .../Haskell/TH/{Lib.hs => Lib/Internal.hs} | 267 +++---- libraries/template-haskell/changelog.md | 8 + libraries/template-haskell/template-haskell.cabal | 2 + testsuite/tests/quotes/TH_localname.stderr | 2 +- testsuite/tests/th/T13642.hs | 4 +- testsuite/tests/th/T13642.stderr | 4 - testsuite/tests/th/T7276.stderr | 4 +- testsuite/tests/th/all.T | 2 +- 11 files changed, 280 insertions(+), 1156 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 b3b564fbc0ceb06e6a880289935449fda7d33f31 From git at git.haskell.org Fri Jul 28 15:52:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 15:52:35 +0000 (UTC) Subject: [commit: ghc] master: Add regression tests for #13601, #13780, #13877 (424ecad) Message-ID: <20170728155235.507CA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/424ecadbb3d06f4d4e0813de670369893e1da2a9/ghc >--------------------------------------------------------------- commit 424ecadbb3d06f4d4e0813de670369893e1da2a9 Author: Ryan Scott Date: Fri Jul 28 11:47:38 2017 -0400 Add regression tests for #13601, #13780, #13877 Summary: Some recent commits happened to fix other issues: * c2417b87ff59c92fbfa8eceeff2a0d6152b11a47 fixed #13601 and #13780 * 8e15e3d370e9c253ae0dbb330e25b72cb00cdb76 fixed the original program in #13877 Let's add regression tests for each of these to ensure they stay fixed. Test Plan: make test TEST="T13601 T13780a T13780c T13877" Reviewers: goldfire, bgamari, austin Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13601, #13780, #13877 Differential Revision: https://phabricator.haskell.org/D3794 >--------------------------------------------------------------- 424ecadbb3d06f4d4e0813de670369893e1da2a9 testsuite/tests/dependent/should_fail/T13601.hs | 47 ++++++++++++++ .../tests/dependent/should_fail/T13601.stderr | 6 ++ testsuite/tests/dependent/should_fail/T13780a.hs | 9 +++ .../tests/dependent/should_fail/T13780a.stderr | 6 ++ testsuite/tests/dependent/should_fail/T13780b.hs | 10 +++ testsuite/tests/dependent/should_fail/T13780c.hs | 12 ++++ .../tests/dependent/should_fail/T13780c.stderr | 12 ++++ testsuite/tests/dependent/should_fail/all.T | 4 ++ .../tests/indexed-types/should_fail/T13877.hs | 74 ++++++++++++++++++++++ .../tests/indexed-types/should_fail/T13877.stderr | 31 +++++++++ testsuite/tests/indexed-types/should_fail/all.T | 1 + 11 files changed, 212 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 424ecadbb3d06f4d4e0813de670369893e1da2a9 From git at git.haskell.org Fri Jul 28 16:37:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:37:06 +0000 (UTC) Subject: [commit: ghc] master: Switched out optparse for argparse in runtests.py (5e940bd) Message-ID: <20170728163706.145FB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5e940bd3d554729ce650008a72b4f82a78578a7b/ghc >--------------------------------------------------------------- commit 5e940bd3d554729ce650008a72b4f82a78578a7b Author: Jared Weakly Date: Thu Jul 27 14:33:16 2017 -0400 Switched out optparse for argparse in runtests.py Tangentially related to my prior work on trac ticket #12758. Signed-off-by: Jared Weakly Reviewers: austin, bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3792 >--------------------------------------------------------------- 5e940bd3d554729ce650008a72b4f82a78578a7b testsuite/driver/runtests.py | 134 ++++++++++++++++++------------------------- testsuite/mk/test.mk | 6 +- 2 files changed, 60 insertions(+), 80 deletions(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index 7e4f375..f7064a5 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -6,11 +6,11 @@ from __future__ import print_function +import argparse import signal import sys import os import string -import getopt import shutil import tempfile import time @@ -41,81 +41,61 @@ def signal_handler(signal, frame): # ----------------------------------------------------------------------------- # cmd-line options -long_options = [ - "configfile=", # config file - "config=", # config field - "rootdir=", # root of tree containing tests (default: .) - "summary-file=", # file in which to save the (human-readable) summary - "no-print-summary=", # should we print the summary? - "only=", # just this test (can be give multiple --only= flags) - "way=", # just this way - "skipway=", # skip this way - "threads=", # threads to run simultaneously - "check-files-written", # check files aren't written by multiple tests - "verbose=", # verbose (0,1,2 so far) - "skip-perf-tests", # skip performance tests - ] - -opts, args = getopt.getopt(sys.argv[1:], "e:", long_options) - -for opt,arg in opts: - if opt == '--configfile': - exec(open(arg).read()) - - # -e is a string to execute from the command line. For example: - # testframe -e 'config.compiler=ghc-5.04' - if opt == '-e': - exec(arg) - - if opt == '--config': - field, value = arg.split('=', 1) - setattr(config, field, value) - - if opt == '--rootdir': - config.rootdirs.append(arg) - - if opt == '--summary-file': - config.summary_file = arg - - if opt == '--no-print-summary': - config.no_print_summary = True - - if opt == '--only': - config.run_only_some_tests = True - config.only.add(arg) - - if opt == '--way': - if (arg not in config.run_ways and arg not in config.compile_ways and arg not in config.other_ways): - sys.stderr.write("ERROR: requested way \'" + - arg + "\' does not exist\n") - sys.exit(1) - config.cmdline_ways = [arg] + config.cmdline_ways - if (arg in config.other_ways): - config.run_ways = [arg] + config.run_ways - config.compile_ways = [arg] + config.compile_ways - - if opt == '--skipway': - if (arg not in config.run_ways and arg not in config.compile_ways and arg not in config.other_ways): - sys.stderr.write("ERROR: requested way \'" + - arg + "\' does not exist\n") - sys.exit(1) - config.other_ways = [w for w in config.other_ways if w != arg] - config.run_ways = [w for w in config.run_ways if w != arg] - config.compile_ways = [w for w in config.compile_ways if w != arg] - - if opt == '--threads': - config.threads = int(arg) - config.use_threads = 1 - - if opt == '--skip-perf-tests': - config.skip_perf_tests = True - - if opt == '--verbose': - if arg not in ["0","1","2","3","4","5"]: - sys.stderr.write("ERROR: requested verbosity %s not supported, use 0,1,2,3,4 or 5" % arg) - sys.exit(1) - config.verbose = int(arg) - +parser = argparse.ArgumentParser(description="GHC's testsuite driver", + allow_abbrev=False) + +parser.add_argument("-e", action='append', help="A string to execute from the command line.") +parser.add_argument("--config-file", action="append", help="config file") +parser.add_argument("--config", action='append', help="config field") +parser.add_argument("--rootdir", action='append', help="root of tree containing tests (default: .)") +parser.add_argument("--summary-file", help="file in which to save the (human-readable) summary") +parser.add_argument("--no-print-summary", action="store_true", help="should we print the summary?") +parser.add_argument("--only", action="append", help="just this test (can be give multiple --only= flags)") +parser.add_argument("--way", choices=config.run_ways+config.compile_ways+config.other_ways, help="just this way") +parser.add_argument("--skipway", action="append", choices=config.run_ways+config.compile_ways+config.other_ways, help="skip this way") +parser.add_argument("--threads", type=int, help="threads to run simultaneously") +parser.add_argument("--check-files-written", help="check files aren't written by multiple tests") # NOTE: This doesn't seem to exist? +parser.add_argument("--verbose", type=int, choices=[0,1,2,3,4,5], help="verbose (Values 0 through 5 accepted)") +parser.add_argument("--skip-perf-tests", action="store_true", help="skip performance tests") + +args = parser.parse_args() + +for e in args.e: + exec(e) + +for arg in args.config_file: + exec(open(arg).read()) + +for arg in args.config: + field, value = arg.split('=', 1) + setattr(config, field, value) + +config.rootdirs = args.rootdir +config.summary_file = args.summary_file +config.no_print_summary = args.no_print_summary + +if args.only: + config.only = args.only + config.run_only_some_tests = True + +if args.way: + config.cmdline_ways = [args.way] + config.cmdline_ways + if (args.way in config.other_ways): + config.run_ways = [args.way] + config.run_ways + config.compile_ways = [args.way] + config.compile_ways + +if args.skipway: + config.other_ways = [w for w in config.other_ways if w != args.skipway] + config.run_ways = [w for w in config.run_ways if w != args.skipway] + config.compile_ways = [w for w in config.compile_ways if w != args.skipway] + +if args.threads: + config.threads = args.threads + config.use_threads = True + +if args.verbose: + config.verbose = args.verbose +config.skip_perf_tests = args.skip_perf_tests config.cygwin = False config.msys = False @@ -326,7 +306,7 @@ else: summary(t, sys.stdout, config.no_print_summary) - if config.summary_file != '': + if config.summary_file: with open(config.summary_file, 'w') as file: summary(t, file) diff --git a/testsuite/mk/test.mk b/testsuite/mk/test.mk index a44e200..6c39636 100644 --- a/testsuite/mk/test.mk +++ b/testsuite/mk/test.mk @@ -73,7 +73,7 @@ else dllext = .so endif -RUNTEST_OPTS += -e ghc_compiler_always_flags="'$(TEST_HC_OPTS)'" +RUNTEST_OPTS += -e "ghc_compiler_always_flags='$(TEST_HC_OPTS)'" RUNTEST_OPTS += -e config.compiler_debugged=$(GhcDebugged) @@ -214,7 +214,7 @@ endif RUNTEST_OPTS += \ --rootdir=. \ - --configfile=$(CONFIG) \ + --config-file=$(CONFIG) \ -e 'config.confdir="$(CONFIGDIR)"' \ -e 'config.platform="$(TARGETPLATFORM)"' \ -e 'config.os="$(TargetOS_CPP)"' \ @@ -252,7 +252,7 @@ RUNTEST_OPTS += \ endif ifeq "$(NO_PRINT_SUMMARY)" "YES" RUNTEST_OPTS += \ - --no-print-summary 1 + --no-print-summary endif RUNTEST_OPTS += \ From git at git.haskell.org Fri Jul 28 16:37:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:37:09 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Produce JUnit output (54d3a1f) Message-ID: <20170728163709.29B103A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/54d3a1fdeb7044a1d9bb025d4880d08c708b4cd0/ghc >--------------------------------------------------------------- commit 54d3a1fdeb7044a1d9bb025d4880d08c708b4cd0 Author: Ben Gamari Date: Fri Jul 28 11:40:42 2017 -0400 testsuite: Produce JUnit output Test Plan: Validate, try ingesting into Jenkins. Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #13716 Differential Revision: https://phabricator.haskell.org/D3796 >--------------------------------------------------------------- 54d3a1fdeb7044a1d9bb025d4880d08c708b4cd0 .gitignore | 1 + testsuite/driver/junit.py | 38 ++++++++++++++++++++++++++++++++++++++ testsuite/driver/runtests.py | 5 +++++ testsuite/driver/testglobals.py | 1 + testsuite/driver/testlib.py | 1 + testsuite/mk/test.mk | 4 ++++ validate | 2 ++ 7 files changed, 52 insertions(+) diff --git a/.gitignore b/.gitignore index 16071f6..073c5a3 100644 --- a/.gitignore +++ b/.gitignore @@ -171,6 +171,7 @@ _darcs/ /rts/package.conf.install.raw /stage3.package.conf /testsuite_summary*.txt +/testsuite*.xml /testlog* /utils/mkUserGuidePart/mkUserGuidePart.cabal /utils/runghc/runghc.cabal diff --git a/testsuite/driver/junit.py b/testsuite/driver/junit.py new file mode 100644 index 0000000..01a5f47 --- /dev/null +++ b/testsuite/driver/junit.py @@ -0,0 +1,38 @@ +from datetime import datetime +import xml.etree.ElementTree as ET + +def junit(t): + testsuites = ET.Element('testsuites') + testsuite = ET.SubElement(testsuites, 'testsuite', + id = "0", + package = 'ghc', + tests = str(t.total_tests), + failures = str(len(t.unexpected_failures) + len(t.unexpected_stat_failures)), + errors = str(len(t.framework_failures)), + timestamp = datetime.now().isoformat()) + + for result, group in [('stat failure', t.unexpected_stat_failures), + ('unexpected failure', t.unexpected_failures)]: + for (directory, testname, reason, way) in group: + testcase = ET.SubElement(testsuite, 'testcase', + classname = testname, + name = way) + result = ET.SubElement(testcase, 'failure', + type = result, + message = reason) + + for (directory, testname, reason, way) in t.framework_failures: + testcase = ET.SubElement(testsuite, 'testcase', + classname = testname, + name = way) + result = ET.SubElement(testcase, 'error', + type = "framework failure", + message = reason) + + for (directory, testname, way) in t.expected_passes: + testcase = ET.SubElement(testsuite, 'testcase', + classname = testname, + name = way) + + return ET.ElementTree(testsuites) + diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index f7064a5..f0c635f 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -26,6 +26,7 @@ import subprocess from testutil import * from testglobals import * +from junit import junit # Readline sometimes spews out ANSI escapes for some values of TERM, # which result in test failures. Thus set TERM to a nice, simple, safe @@ -57,6 +58,7 @@ parser.add_argument("--threads", type=int, help="threads to run simultaneously") parser.add_argument("--check-files-written", help="check files aren't written by multiple tests") # NOTE: This doesn't seem to exist? parser.add_argument("--verbose", type=int, choices=[0,1,2,3,4,5], help="verbose (Values 0 through 5 accepted)") parser.add_argument("--skip-perf-tests", action="store_true", help="skip performance tests") +parser.add_argument("--junit", type=argparse.FileType('wb'), help="output testsuite summary in JUnit format") args = parser.parse_args() @@ -310,6 +312,9 @@ else: with open(config.summary_file, 'w') as file: summary(t, file) + if args.junit: + junit(t).write(args.junit) + cleanup_and_exit(0) # Note [Running tests in /tmp] diff --git a/testsuite/driver/testglobals.py b/testsuite/driver/testglobals.py index fc050e6..5e7142d 100644 --- a/testsuite/driver/testglobals.py +++ b/testsuite/driver/testglobals.py @@ -140,6 +140,7 @@ class TestRun: self.framework_failures = [] self.framework_warnings = [] + self.expected_passes = [] self.unexpected_passes = [] self.unexpected_failures = [] self.unexpected_stat_failures = [] diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 26e3d17..15c773e 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -863,6 +863,7 @@ def do_test(name, way, func, args, files): if passFail == 'pass': if _expect_pass(way): + t.expected_passes.append((directory, name, way)) t.n_expected_passes += 1 else: if_verbose(1, '*** unexpected pass for %s' % full_name) diff --git a/testsuite/mk/test.mk b/testsuite/mk/test.mk index 6c39636..a21c4bb 100644 --- a/testsuite/mk/test.mk +++ b/testsuite/mk/test.mk @@ -246,6 +246,10 @@ RUNTEST_OPTS += \ RUNTEST_OPTS += -e "config.stage=$(GhcStage)" +ifneq "$(JUNIT_FILE)" "" +RUNTEST_OPTS += \ + --junit "$(JUNIT_FILE)" +endif ifneq "$(SUMMARY_FILE)" "" RUNTEST_OPTS += \ --summary-file "$(SUMMARY_FILE)" diff --git a/validate b/validate index 09f4fd2..d885bd7 100755 --- a/validate +++ b/validate @@ -296,6 +296,7 @@ rm -f testsuite_summary.txt testsuite_summary_stage1.txt $make -C testsuite/tests $BINDIST $PYTHON_ARG \ $MAKE_TEST_TARGET stage=2 LOCAL=0 $TEST_VERBOSITY THREADS=$threads \ NO_PRINT_SUMMARY=YES SUMMARY_FILE=../../testsuite_summary.txt \ + JUNIT_FILE=../../testsuite.xml \ 2>&1 | tee testlog # Run a few tests using the stage1 compiler. @@ -304,6 +305,7 @@ $make -C testsuite/tests $BINDIST $PYTHON_ARG \ $make -C testsuite/tests/stage1 $PYTHON_ARG \ $MAKE_TEST_TARGET stage=1 LOCAL=0 $TEST_VERBOSITY THREADS=$threads \ NO_PRINT_SUMMARY=YES SUMMARY_FILE=../../../testsuite_summary_stage1.txt \ + JUNIT_FILE=../../../testsuite_stage1.xml \ 2>&1 | tee testlog-stage1 echo From git at git.haskell.org Fri Jul 28 16:37:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:37:12 +0000 (UTC) Subject: [commit: ghc] master: ByteCodeGen: use byte indexing for BCenv (dac4b9d) Message-ID: <20170728163712.03BF13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dac4b9d3cdca83c99d5d894d2743cc0bbca450ac/ghc >--------------------------------------------------------------- commit dac4b9d3cdca83c99d5d894d2743cc0bbca450ac Author: Michal Terepeta Date: Fri Jul 28 11:47:28 2017 -0400 ByteCodeGen: use byte indexing for BCenv This is another change needed for #13825 (also based on D38 by Simon Marlow). With the change, we count the stack depth in bytes (instead of words). We also introduce some `newtype`s to help with the change. Note that this only changes how `ByteCodeGen` works and shouldn't affect the generated bytecode. Signed-off-by: Michal Terepeta Test Plan: ./validate Reviewers: bgamari, simonmar, austin, hvr Reviewed By: bgamari, simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13825 Differential Revision: https://phabricator.haskell.org/D3746 >--------------------------------------------------------------- dac4b9d3cdca83c99d5d894d2743cc0bbca450ac compiler/ghci/ByteCodeGen.hs | 467 ++++++++++++++++++++++++++----------------- 1 file changed, 283 insertions(+), 184 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 dac4b9d3cdca83c99d5d894d2743cc0bbca450ac From git at git.haskell.org Fri Jul 28 16:37:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:37:14 +0000 (UTC) Subject: [commit: ghc] master: Fix lld detection if both gold and lld are found (2974f81) Message-ID: <20170728163714.B87A93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2974f81f8c3529657a0b808b8415a4d2ad9ed6d1/ghc >--------------------------------------------------------------- commit 2974f81f8c3529657a0b808b8415a4d2ad9ed6d1 Author: Ben Gamari Date: Fri Jul 28 11:48:52 2017 -0400 Fix lld detection if both gold and lld are found If you have ld.gold and ld.lld, then ld.gold will be selected by the detection logic. This patch prioritizes lld by changing the order. The rationale for checking lld first is that it's (right now) not part of, say, a default Linux distro installation and if it's available, it's very likely that it was installed explicitly and should be seen as a sign of preference. On FreeBSD LLVM is the (default) base toolchain and the changed order makes sense there as well, since ld.gold can be available in /usr/local via ports/pkg. I don't have access to macOS and can't say anything about their LLVM toolchain. At some point we could add a check for LD=ld.lld or LD=ld.gold as an optional override to explicitly select a linker. Since I cannot really remove gcc on Linux, this was the only way to configure GHC to use ld.lld. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, erikd Tags: PHID-PROJ-5azim3sqhsf7wzvlvaag Differential Revision: https://phabricator.haskell.org/D3790 >--------------------------------------------------------------- 2974f81f8c3529657a0b808b8415a4d2ad9ed6d1 aclocal.m4 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/aclocal.m4 b/aclocal.m4 index a9788bf..0389474 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2283,7 +2283,7 @@ AC_DEFUN([FIND_LD],[ [enable_ld_override=yes]) if test "x$enable_ld_override" = "xyes"; then - AC_CHECK_TARGET_TOOLS([TmpLd], [ld.gold ld.lld ld]) + AC_CHECK_TARGET_TOOLS([TmpLd], [ld.lld ld.gold ld]) out=`$TmpLd --version` case $out in From git at git.haskell.org Fri Jul 28 16:37:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:37:17 +0000 (UTC) Subject: [commit: ghc] master: Add “BINARY_DIST_DIR” to Makefile (274e9b2) Message-ID: <20170728163717.73B213A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/274e9b27de30e1b7d5db8cb97b34d53ae9609a9b/ghc >--------------------------------------------------------------- commit 274e9b27de30e1b7d5db8cb97b34d53ae9609a9b Author: Moritz Angermann Date: Fri Jul 28 11:44:33 2017 -0400 Add “BINARY_DIST_DIR” to Makefile This allows to customize the location where binary distributions are placed with `make binary-dist`. E.g. using: ``` BINARY_DIST_DIR=/path/to/bindists make binary-dist ``` will place binary dists outside of the source tree into the given folder. This change falls back to ".", which is the old behaviour. Test Plan: build binary-dist Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3798 >--------------------------------------------------------------- 274e9b27de30e1b7d5db8cb97b34d53ae9609a9b Makefile | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/Makefile b/Makefile index 9b888e7..8046e36 100644 --- a/Makefile +++ b/Makefile @@ -129,9 +129,15 @@ endif @echo "===--- building final phase" $(MAKE) --no-print-directory -f ghc.mk phase=final $@ +# if BINARY_DIST_DIR is not set, assume we want the old +# behaviour of placing the binary dist into the current +# directory. Provide BINARY_DIST_DIR to put the final +# binary distribution elsewhere. +BINARY_DIST_DIR ?= . + .PHONY: binary-dist binary-dist: binary-dist-prep - mv bindistprep/*.tar.$(TAR_COMP_EXT) . + mv bindistprep/*.tar.$(TAR_COMP_EXT) "$(BINARY_DIST_DIR)" .PHONY: binary-dist-prep binary-dist-prep: From git at git.haskell.org Fri Jul 28 16:37:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:37:20 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add test for #14028 (262bb95) Message-ID: <20170728163720.CC9A13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/262bb95f5e00eea783d3e756fe86d96839be45d7/ghc >--------------------------------------------------------------- commit 262bb95f5e00eea783d3e756fe86d96839be45d7 Author: Ben Gamari Date: Fri Jul 28 11:44:20 2017 -0400 testsuite: Add test for #14028 Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #14028 Differential Revision: https://phabricator.haskell.org/D3788 >--------------------------------------------------------------- 262bb95f5e00eea783d3e756fe86d96839be45d7 testsuite/tests/quasiquotation/Makefile | 4 ++++ testsuite/tests/quasiquotation/T14028.hs | 8 ++++++++ testsuite/tests/quasiquotation/T14028C.c | 5 +++++ testsuite/tests/quasiquotation/T14028Quote.hs | 6 ++++++ testsuite/tests/quasiquotation/all.T | 4 ++++ 5 files changed, 27 insertions(+) diff --git a/testsuite/tests/quasiquotation/Makefile b/testsuite/tests/quasiquotation/Makefile index 8e2e7e7..ebc91d2 100644 --- a/testsuite/tests/quasiquotation/Makefile +++ b/testsuite/tests/quasiquotation/Makefile @@ -9,3 +9,7 @@ T4150: '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -c T4150A.hs -'$(TEST_HC)' $(TEST_HC_OPTS) -v0 -c T4150.hs +T14028: + '$(TEST_HC)' $(TEST_HC_OPTS) T14028Quote.hs + '$(TEST_HC)' $(TEST_HC_OPTS) -c T14028C.c + '$(TEST_HC)' $(TEST_HC_OPTS) -fexternal-interpreter T14028 T14028C.o diff --git a/testsuite/tests/quasiquotation/T14028.hs b/testsuite/tests/quasiquotation/T14028.hs new file mode 100644 index 0000000..5313df6 --- /dev/null +++ b/testsuite/tests/quasiquotation/T14028.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE QuasiQuotes #-} + +import T14028Quote + +s :: String +s = [here|goes nothing|] + +main = putStrLn s diff --git a/testsuite/tests/quasiquotation/T14028C.c b/testsuite/tests/quasiquotation/T14028C.c new file mode 100644 index 0000000..0115013 --- /dev/null +++ b/testsuite/tests/quasiquotation/T14028C.c @@ -0,0 +1,5 @@ +#include + +void hi() { + puts("Hello, World!"); +} diff --git a/testsuite/tests/quasiquotation/T14028Quote.hs b/testsuite/tests/quasiquotation/T14028Quote.hs new file mode 100644 index 0000000..01413ec --- /dev/null +++ b/testsuite/tests/quasiquotation/T14028Quote.hs @@ -0,0 +1,6 @@ +module T14028Quote where +import Language.Haskell.TH +import Language.Haskell.TH.Quote + +here :: QuasiQuoter +here = QuasiQuoter { quoteExp = litE . stringL } diff --git a/testsuite/tests/quasiquotation/all.T b/testsuite/tests/quasiquotation/all.T index 84d25f8..a10b8e4 100644 --- a/testsuite/tests/quasiquotation/all.T +++ b/testsuite/tests/quasiquotation/all.T @@ -6,3 +6,7 @@ test('T7918', [req_interp, extra_run_opts('"' + config.libdir + '"'), only_ways(config.ghc_th_way), unless(have_dynamic(), skip)], compile_and_run, ['-package ghc ' + config.ghc_th_way_flags]) +test('T14028', + [req_interp, only_ways(config.ghc_th_way)], + run_command, + ['$MAKE -s --no-print-directory T14028']) From git at git.haskell.org Fri Jul 28 16:41:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:41:19 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Testing (b693d6d) Message-ID: <20170728164119.2836C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/b693d6dad6302ff58888caf0fec0dfcfd8a8b303/ghc >--------------------------------------------------------------- commit b693d6dad6302ff58888caf0fec0dfcfd8a8b303 Author: Ben Gamari Date: Fri Apr 28 09:53:13 2017 -0400 Testing >--------------------------------------------------------------- b693d6dad6302ff58888caf0fec0dfcfd8a8b303 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 Fri Jul 28 16:41:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:41:21 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (c436d8c) Message-ID: <20170728164121.DB36D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c436d8caaca9846df1c8f68e277377163bc0653f/ghc >--------------------------------------------------------------- commit c436d8caaca9846df1c8f68e277377163bc0653f Author: Ben Gamari Date: Sun Jun 4 11:18:23 2017 -0400 Debug >--------------------------------------------------------------- c436d8caaca9846df1c8f68e277377163bc0653f Jenkinsfile | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index a1a6b13..c924e85 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -223,8 +223,9 @@ def withGhcSrcDist(Closure f) { } def metadata = readJSON file: 'src-dist.json' + sh "cat src-dist.json" echo "${metadata}" - sh "${metadata.dirName}" + sh "echo ${metadata.dirName}; ls ${metadata.dirName}" dir(metadata.dirName) { f() } From git at git.haskell.org Fri Jul 28 16:41:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:41:27 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarName (fb37013) Message-ID: <20170728164127.522D73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/fb370132abe8f1a9df0e1dc750c8c133ac1e3c42/ghc >--------------------------------------------------------------- commit fb370132abe8f1a9df0e1dc750c8c133ac1e3c42 Author: Ben Gamari Date: Sat Jun 3 21:33:12 2017 -0400 Fix tarName >--------------------------------------------------------------- fb370132abe8f1a9df0e1dc750c8c133ac1e3c42 Jenkinsfile | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index b40186c..830afd1 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -156,14 +156,13 @@ def buildGhc(params) { sh "${makeCmd} binary-dist" def json = new JSONObject() def tarPath = getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') - def tarName = sh "basename ${tarPath}" + def tarName = sh(script: "basename ${tarPath}", returnStdout: true) 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')) echo "${json}" - echo json.toString() writeJSON(file: 'bindist.json', json: json) // 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 Fri Jul 28 16:41:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:41:24 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix missing binding (381225c) Message-ID: <20170728164124.980353A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/381225c715957c42260ef2d9082295ac17fe6132/ghc >--------------------------------------------------------------- commit 381225c715957c42260ef2d9082295ac17fe6132 Author: Ben Gamari Date: Wed May 31 11:36:00 2017 -0400 Fix missing binding >--------------------------------------------------------------- 381225c715957c42260ef2d9082295ac17fe6132 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 Fri Jul 28 16:41:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:41:30 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Cross (697490b) Message-ID: <20170728164130.0D6123A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/697490b40b4453f35d3f9bc6d09daf4aeb9d22b0/ghc >--------------------------------------------------------------- commit 697490b40b4453f35d3f9bc6d09daf4aeb9d22b0 Author: Ben Gamari Date: Thu May 18 01:00:42 2017 -0400 Cross >--------------------------------------------------------------- 697490b40b4453f35d3f9bc6d09daf4aeb9d22b0 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 Fri Jul 28 16:41:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:41:32 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Introduce echo! make target (fcf5edf) Message-ID: <20170728164132.BC7443A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/fcf5edf317c6d363ca80ff6fb543b6128e48c278/ghc >--------------------------------------------------------------- commit fcf5edf317c6d363ca80ff6fb543b6128e48c278 Author: Ben Gamari Date: Sun Jun 4 10:27:24 2017 -0400 Introduce echo! make target This is analogous to show! >--------------------------------------------------------------- fcf5edf317c6d363ca80ff6fb543b6128e48c278 Makefile | 4 ++++ ghc.mk | 4 ++++ 2 files changed, 8 insertions(+) diff --git a/Makefile b/Makefile index 8046e36..89361d9 100644 --- a/Makefile +++ b/Makefile @@ -173,6 +173,10 @@ $(filter clean_%, $(MAKECMDGOALS)) : clean_% : bootstrapping-files show echo: $(MAKE) --no-print-directory -f ghc.mk $@ +.PHONY: echo! +echo!: + @$(MAKE) --no-print-directory -f ghc.mk echo NO_INCLUDE_PKGDATA=YES + .PHONY: show! show!: $(MAKE) --no-print-directory -f ghc.mk show NO_INCLUDE_PKGDATA=YES diff --git a/ghc.mk b/ghc.mk index 4eb1658..b3410ac 100644 --- a/ghc.mk +++ b/ghc.mk @@ -260,6 +260,10 @@ ifeq "$(findstring show,$(MAKECMDGOALS))" "show" NO_INCLUDE_DEPS = YES # We want package-data.mk for show endif +ifeq "$(findstring echo,$(MAKECMDGOALS))" "echo" +NO_INCLUDE_DEPS = YES +# We want package-data.mk for show +endif # ----------------------------------------------------------------------------- # Ways From git at git.haskell.org Fri Jul 28 16:41:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:41:35 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Hmm (d713c32) Message-ID: <20170728164135.7CCF43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d713c3249c9992c29b1626eaed4aa411a3f8e1b9/ghc >--------------------------------------------------------------- commit d713c3249c9992c29b1626eaed4aa411a3f8e1b9 Author: Ben Gamari Date: Mon May 29 16:45:16 2017 -0400 Hmm >--------------------------------------------------------------- d713c3249c9992c29b1626eaed4aa411a3f8e1b9 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 Fri Jul 28 16:41:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:41:38 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix testsuite (7ec638a) Message-ID: <20170728164138.393913A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7ec638a16e6d3c376a71e8c0539a9e421e96fdb0/ghc >--------------------------------------------------------------- commit 7ec638a16e6d3c376a71e8c0539a9e421e96fdb0 Author: Ben Gamari Date: Tue May 30 12:11:16 2017 -0400 Fix testsuite >--------------------------------------------------------------- 7ec638a16e6d3c376a71e8c0539a9e421e96fdb0 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 Fri Jul 28 16:41:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:41:40 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Clean (72a7915) Message-ID: <20170728164140.EF18D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/72a79159f25aec3b9828049752cf4941bcf9a775/ghc >--------------------------------------------------------------- commit 72a79159f25aec3b9828049752cf4941bcf9a775 Author: Ben Gamari Date: Tue May 30 00:29:29 2017 -0400 Clean >--------------------------------------------------------------- 72a79159f25aec3b9828049752cf4941bcf9a775 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 Fri Jul 28 16:41:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:41:43 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Reenable everything else (03a0526) Message-ID: <20170728164143.ABB2A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/03a052683c53ea3813bc60e8d4709fbe2d7a086a/ghc >--------------------------------------------------------------- commit 03a052683c53ea3813bc60e8d4709fbe2d7a086a Author: Ben Gamari Date: Mon May 29 22:45:19 2017 -0400 Reenable everything else >--------------------------------------------------------------- 03a052683c53ea3813bc60e8d4709fbe2d7a086a 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 Fri Jul 28 16:41:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:41:46 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Unregisterised (588d91c) Message-ID: <20170728164146.6566F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/588d91c7227f0dab99e501f6b12ab3da9893d3d0/ghc >--------------------------------------------------------------- commit 588d91c7227f0dab99e501f6b12ab3da9893d3d0 Author: Ben Gamari Date: Thu May 18 01:55:35 2017 -0400 Unregisterised >--------------------------------------------------------------- 588d91c7227f0dab99e501f6b12ab3da9893d3d0 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 Fri Jul 28 16:41:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:41:49 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (184f683) Message-ID: <20170728164149.208CD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/184f68314be3b9d1ac424296567cdbceb726a67d/ghc >--------------------------------------------------------------- commit 184f68314be3b9d1ac424296567cdbceb726a67d Author: Ben Gamari Date: Mon May 29 15:49:33 2017 -0400 Debug >--------------------------------------------------------------- 184f68314be3b9d1ac424296567cdbceb726a67d 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 Fri Jul 28 16:41:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:41:51 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix JSON serialization (b216799) Message-ID: <20170728164151.CDCEA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/b21679988dcd00cc83c8f25452d03cf8922f7191/ghc >--------------------------------------------------------------- commit b21679988dcd00cc83c8f25452d03cf8922f7191 Author: Ben Gamari Date: Wed May 31 10:43:24 2017 -0400 Fix JSON serialization >--------------------------------------------------------------- b21679988dcd00cc83c8f25452d03cf8922f7191 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 Fri Jul 28 16:41:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:41:54 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add THREADS parameter (0cf1486) Message-ID: <20170728164154.8A4E93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0cf1486e1cfdb7577f1eeea9c2e3d27c2922e630/ghc >--------------------------------------------------------------- commit 0cf1486e1cfdb7577f1eeea9c2e3d27c2922e630 Author: Ben Gamari Date: Sat May 13 11:59:37 2017 -0400 Add THREADS parameter >--------------------------------------------------------------- 0cf1486e1cfdb7577f1eeea9c2e3d27c2922e630 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 Fri Jul 28 16:41:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:41:57 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Build from source distribution (55389c2) Message-ID: <20170728164157.475413A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/55389c2ae3df118f351555d178a4a0aa4d75a06e/ghc >--------------------------------------------------------------- commit 55389c2ae3df118f351555d178a4a0aa4d75a06e Author: Ben Gamari Date: Mon May 29 13:55:58 2017 -0400 Build from source distribution >--------------------------------------------------------------- 55389c2ae3df118f351555d178a4a0aa4d75a06e Jenkinsfile | 181 ++++++++++++++++++++++++++++++++++++++---------------------- 1 file changed, 116 insertions(+), 65 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index fa710c3..3b31238 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -18,6 +18,33 @@ properties( ]) ]) + +stage("Build source distribution") { + node(label: 'linux') { + stage("Checking out tree") { + checkout scm + sh """ + git submodule update --init --recursive + mk/get-win32-tarballs.sh fetch all + """ + } + stage("Configuring tree") { + sh """ + ./boot + ./configure + """ + } + stage("Build tarballs") { + sh "make sdist" + sh "mv sdistprep/ghc-*.tar.xz ghc-src.tar.xz" + sh "mv sdistprep/ghc-*-testsuite.tar.xz ghc-testsuite.tar.xz" + sh "mv sdistprep/ghc-*-windows-extra-src-*.tar.xz ghc-win32-tarballs.tar.xz" + stash(name: 'source-dist', includes: 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz') + stash(name: 'testsuite-dist', includes: 'ghc-testsuite.tar.xz') + } + } +} + parallel ( "linux x86-64" : { node(label: 'linux && amd64') { @@ -103,70 +130,66 @@ def buildGhc(params) { boolean disableLargeAddrSpace = params?.disableLargeAddrSpace ?: false String makeCmd = params?.makeCmd ?: 'make' - stage('Checkout') { - checkout scm - sh "git submodule update --init --recursive" - //sh "${makeCmd} distclean" - } + withGhcSrcDist() { + stage('Configure') { + def speed = 'NORMAL' + if (params.nightly) { + speed = 'SLOW' + } + build_mk = """ + Validating=YES + ValidateSpeed=${speed} + ValidateHpc=NO + BUILD_DPH=NO + """ + if (cross) { + 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) - stage('Configure') { - def speed = 'NORMAL' - if (params.nightly) { - speed = 'SLOW' - } - build_mk = """ - Validating=YES - ValidateSpeed=${speed} - ValidateHpc=NO - BUILD_DPH=NO - """ - if (cross) { - build_mk += """ - # Cross compiling - HADDOCK_DOCS=NO - BUILD_SPHINX_HTML=NO - BUILD_SPHINX_PDF=NO - INTEGER_LIBRARY=integer-simple - WITH_TERMINFO=NO - """ + def configure_opts = [] + if (cross) { + configure_opts += '--target=${targetTriple}' + } + if (disableLargeAddrSpace) { + configure_opts += '--disable-large-address-space' + } + if (unreg) { + configure_opts += '--enable-unregisterised' + } + sh """ + ./boot + ./configure ${configure_opts.join(' ')} + """ } - writeFile(file: 'mk/build.mk', text: build_mk) - def configure_opts = ['--enable-tarballs-autodownload'] - if (cross) { - configure_opts += '--target=${targetTriple}' - } - if (disableLargeAddrSpace) { - configure_opts += '--disable-large-address-space' - } - if (unreg) { - configure_opts += '--enable-unregisterised' + stage('Build') { + sh "${makeCmd} -j${env.THREADS}" } - sh """ - ./boot - ./configure ${configure_opts.join(' ')} - """ - } - - stage('Build') { - sh "${makeCmd} -j${env.THREADS}" - } - stage('Prepare binary distribution') { - sh "${makeCmd} binary-dist" - def json = new JSONObject() - def tarPath = getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') - def tarName = sh(script: "basename ${tarPath}", returnStdout: true) - 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')) - echo "${json}" - writeJSON(file: 'bindist.json', json: 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}" + stage('Prepare binary distribution') { + sh "${makeCmd} binary-dist" + def json = new JSONObject() + def tarPath = getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') + def tarName = sh(script: "basename ${tarPath}", returnStdout: true) + 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')) + echo "${json}" + writeJSON(file: 'bindist.json', json: 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}" + } } } @@ -174,12 +197,9 @@ 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 metadata = readJSON file: "bindist.json" - echo "${metadata}" - sh "tar -xf ${metadata.tarName}" - dir("${metadata.dirName}") { +def withTempDir(String name, Closure f) { + sh "mkdir ${name}" + dir(name) { try { f() } finally { @@ -188,6 +208,37 @@ def withGhcBinDist(String targetTriple, Closure f) { } } +def withGhcSrcDist(Closure f) { + withTempDir('src-dist') { + stage('Unpack source distribution') { + unstash(name: "source-dist") + sh 'tar -xf ghc-src.tar.xz' + sh 'tar -xf ghc-win32-tarballs.tar.xz' + } + dir('ghc-*') { + f() + } + } +} + +def withGhcBinDist(String targetTriple, Closure f) { + withTempDir('bin-dist') { + unstash "bindist-${targetTriple}" + unstash "testsuite-dist" + def metadata = readJSON file: "bindist.json" + echo "${metadata}" + sh "tar -xf ${metadata.tarName}" + sh "tar -xf ghc-testsuite.tar.xz" + dir("${metadata.dirName}") { + try { + f() + } finally { + deleteDir() + } + } + } +} + def testGhc(params) { String targetTriple = params?.targetTriple String makeCmd = params?.makeCmd ?: 'make' From git at git.haskell.org Fri Jul 28 16:42:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:00 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: windows (c96959f) Message-ID: <20170728164200.092123A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c96959fcea9c77f55634fbe3456df409c4e5f0e7/ghc >--------------------------------------------------------------- commit c96959fcea9c77f55634fbe3456df409c4e5f0e7 Author: Ben Gamari Date: Thu May 18 01:55:46 2017 -0400 windows >--------------------------------------------------------------- c96959fcea9c77f55634fbe3456df409c4e5f0e7 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 Fri Jul 28 16:42:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:02 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Try adding type annotation (7d8cc05) Message-ID: <20170728164202.BA5553A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7d8cc05d6ad03b11e6a1fda1b4bb1b6b873a6180/ghc >--------------------------------------------------------------- commit 7d8cc05d6ad03b11e6a1fda1b4bb1b6b873a6180 Author: Ben Gamari Date: Sun Jun 4 11:26:54 2017 -0400 Try adding type annotation >--------------------------------------------------------------- 7d8cc05d6ad03b11e6a1fda1b4bb1b6b873a6180 Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index c924e85..bad87bf 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -196,7 +196,7 @@ def buildGhc(params) { } } -def getMakeValue(String makeCmd, String value) { +String getMakeValue(String makeCmd, String value) { return sh(script: "${makeCmd} -s echo! VALUE=${value}", returnStdout: true) } From git at git.haskell.org Fri Jul 28 16:42:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:05 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Use archiveArtifacts instead of archive (67f51b5) Message-ID: <20170728164205.778563A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/67f51b5831bc8b3d7a3c66de160f811ac70dc3f4/ghc >--------------------------------------------------------------- commit 67f51b5831bc8b3d7a3c66de160f811ac70dc3f4 Author: Ben Gamari Date: Mon May 29 15:44:56 2017 -0400 Use archiveArtifacts instead of archive >--------------------------------------------------------------- 67f51b5831bc8b3d7a3c66de160f811ac70dc3f4 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 Fri Jul 28 16:42:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:08 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (22a9b99) Message-ID: <20170728164208.395D83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/22a9b995a091ca4cc7158e68eb2de5895d0d6b87/ghc >--------------------------------------------------------------- commit 22a9b995a091ca4cc7158e68eb2de5895d0d6b87 Author: Ben Gamari Date: Wed May 17 23:42:59 2017 -0400 Debug >--------------------------------------------------------------- 22a9b995a091ca4cc7158e68eb2de5895d0d6b87 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 Fri Jul 28 16:42:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:10 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring, add Windows, fix cross (c580545) Message-ID: <20170728164210.E75913A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c580545ca966fa490756591efac6f2f22f4a467b/ghc >--------------------------------------------------------------- commit c580545ca966fa490756591efac6f2f22f4a467b Author: Ben Gamari Date: Thu May 18 02:14:40 2017 -0400 Refactoring, add Windows, fix cross >--------------------------------------------------------------- c580545ca966fa490756591efac6f2f22f4a467b 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 Fri Jul 28 16:42:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:13 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Parametrize on make command (270c9f2) Message-ID: <20170728164213.BC7403A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/270c9f232d5bc2a69cbaaa004158afa31ddb76ab/ghc >--------------------------------------------------------------- commit 270c9f232d5bc2a69cbaaa004158afa31ddb76ab Author: Ben Gamari Date: Mon May 29 15:44:39 2017 -0400 Parametrize on make command >--------------------------------------------------------------- 270c9f232d5bc2a69cbaaa004158afa31ddb76ab 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 Fri Jul 28 16:42:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:16 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debuggging (1c6bb01) Message-ID: <20170728164216.7D5043A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/1c6bb013292a70e036d7cab70f866a84deb6f9c2/ghc >--------------------------------------------------------------- commit 1c6bb013292a70e036d7cab70f866a84deb6f9c2 Author: Ben Gamari Date: Sun Jun 4 11:12:23 2017 -0400 Debuggging >--------------------------------------------------------------- 1c6bb013292a70e036d7cab70f866a84deb6f9c2 Jenkinsfile | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 59daa63..a1a6b13 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -223,6 +223,8 @@ def withGhcSrcDist(Closure f) { } def metadata = readJSON file: 'src-dist.json' + echo "${metadata}" + sh "${metadata.dirName}" dir(metadata.dirName) { f() } @@ -237,7 +239,7 @@ def withGhcBinDist(String targetTriple, Closure f) { echo "${metadata}" sh "tar -xf ${metadata.tarName}" sh "tar -xf ghc-testsuite.tar.xz" - dir("${metadata.dirName}") { + dir(metadata.dirName) { try { f() } finally { From git at git.haskell.org Fri Jul 28 16:42:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:19 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Disable non-Windows builds (0a51089) Message-ID: <20170728164219.37CAE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0a510891c656b833b12747f00ffec8d3327909bc/ghc >--------------------------------------------------------------- commit 0a510891c656b833b12747f00ffec8d3327909bc Author: Ben Gamari Date: Mon May 29 19:34:11 2017 -0400 Disable non-Windows builds >--------------------------------------------------------------- 0a510891c656b833b12747f00ffec8d3327909bc 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 Fri Jul 28 16:42:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:21 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarball generation (cd684e9) Message-ID: <20170728164221.EC38D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/cd684e9356c0f7533feae79b791ed5eb25b7fde9/ghc >--------------------------------------------------------------- commit cd684e9356c0f7533feae79b791ed5eb25b7fde9 Author: Ben Gamari Date: Tue May 30 10:43:09 2017 -0400 Fix tarball generation >--------------------------------------------------------------- cd684e9356c0f7533feae79b791ed5eb25b7fde9 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 Fri Jul 28 16:42:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:24 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (0513f72) Message-ID: <20170728164224.A4B8F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0513f72882c7cc3d456f30be862252788fa68a08/ghc >--------------------------------------------------------------- commit 0513f72882c7cc3d456f30be862252788fa68a08 Author: Ben Gamari Date: Thu May 18 02:56:06 2017 -0400 Debug >--------------------------------------------------------------- 0513f72882c7cc3d456f30be862252788fa68a08 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 Fri Jul 28 16:42:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:27 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Be more explicit (e9fded2) Message-ID: <20170728164227.5D6883A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/e9fded2ea4825c2c87ea32c3af6fac4421e976e4/ghc >--------------------------------------------------------------- commit e9fded2ea4825c2c87ea32c3af6fac4421e976e4 Author: Ben Gamari Date: Tue May 30 16:04:31 2017 -0400 Be more explicit >--------------------------------------------------------------- e9fded2ea4825c2c87ea32c3af6fac4421e976e4 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 Fri Jul 28 16:42:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:30 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarball names (a09905f) Message-ID: <20170728164230.15DA53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a09905ff1f06a800cf44570250d99fb678dc8506/ghc >--------------------------------------------------------------- commit a09905ff1f06a800cf44570250d99fb678dc8506 Author: Ben Gamari Date: Sun Jun 4 10:34:37 2017 -0400 Fix tarball names >--------------------------------------------------------------- a09905ff1f06a800cf44570250d99fb678dc8506 Jenkinsfile | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 3b31238..d2f39f3 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -35,10 +35,11 @@ stage("Build source distribution") { """ } stage("Build tarballs") { + def version = getMakeValue('make', 'ProjectVersion') sh "make sdist" - sh "mv sdistprep/ghc-*.tar.xz ghc-src.tar.xz" - sh "mv sdistprep/ghc-*-testsuite.tar.xz ghc-testsuite.tar.xz" - sh "mv sdistprep/ghc-*-windows-extra-src-*.tar.xz ghc-win32-tarballs.tar.xz" + sh "mv sdistprep/ghc-${version}-src.tar.xz ghc-src.tar.xz" + sh "mv sdistprep/ghc-${version}-testsuite.tar.xz ghc-testsuite.tar.xz" + sh "mv sdistprep/ghc-${version}-windows-extra-src.tar.xz ghc-win32-tarballs.tar.xz" stash(name: 'source-dist', includes: 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz') stash(name: 'testsuite-dist', includes: 'ghc-testsuite.tar.xz') } @@ -194,7 +195,7 @@ def buildGhc(params) { } def getMakeValue(String makeCmd, String value) { - return sh(script: "${makeCmd} -s echo VALUE=${value}", returnStdout: true) + return sh(script: "${makeCmd} -s echo! VALUE=${value}", returnStdout: true) } def withTempDir(String name, Closure f) { From git at git.haskell.org Fri Jul 28 16:42:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:32 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: More debugging (a758f59) Message-ID: <20170728164232.C38A13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a758f59aca2254e3f01badcd484432676228b9c0/ghc >--------------------------------------------------------------- commit a758f59aca2254e3f01badcd484432676228b9c0 Author: Ben Gamari Date: Sat Jun 3 17:02:01 2017 -0400 More debugging >--------------------------------------------------------------- a758f59aca2254e3f01badcd484432676228b9c0 Jenkinsfile | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 151bc7b..b40186c 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -162,8 +162,9 @@ def buildGhc(params) { json.put('dirName', getMakeValue(makeCmd, 'BIN_DIST_NAME')) json.put('ghcVersion', getMakeValue(makeCmd, 'ProjectVersion')) json.put('targetPlatform', getMakeValue(makeCmd, 'TARGETPLATFORM')) + echo "${json}" + echo json.toString() writeJSON(file: 'bindist.json', json: json) - 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}" @@ -177,9 +178,9 @@ 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' + echo "${metadata}" sh "tar -xf ${metadata.tarName}" - dir("${metadata.bindistName}") { + dir("${metadata.dirName}") { try { f } finally { From git at git.haskell.org Fri Jul 28 16:42:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:35 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Nailed the Windows issue (770e7f9) Message-ID: <20170728164235.8564C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/770e7f9cd30f041e64a5c069f8886c113a2f13cd/ghc >--------------------------------------------------------------- commit 770e7f9cd30f041e64a5c069f8886c113a2f13cd Author: Ben Gamari Date: Mon May 29 12:48:34 2017 -0400 Nailed the Windows issue >--------------------------------------------------------------- 770e7f9cd30f041e64a5c069f8886c113a2f13cd 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 Fri Jul 28 16:42:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:38 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Handle documentation (318a8e0) Message-ID: <20170728164238.4213D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/318a8e075cade069159ff7cefb7d5dc6a44abdaa/ghc >--------------------------------------------------------------- commit 318a8e075cade069159ff7cefb7d5dc6a44abdaa Author: Ben Gamari Date: Tue May 30 01:46:06 2017 -0400 Handle documentation >--------------------------------------------------------------- 318a8e075cade069159ff7cefb7d5dc6a44abdaa 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 Fri Jul 28 16:42:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:40 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Actually call closure (d9befc5) Message-ID: <20170728164240.F26D93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d9befc54cbe9988b51044de0c33081f7fcfa3891/ghc >--------------------------------------------------------------- commit d9befc54cbe9988b51044de0c33081f7fcfa3891 Author: Ben Gamari Date: Sun Jun 4 01:02:20 2017 -0400 Actually call closure >--------------------------------------------------------------- d9befc54cbe9988b51044de0c33081f7fcfa3891 Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 830afd1..fa710c3 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -181,7 +181,7 @@ def withGhcBinDist(String targetTriple, Closure f) { sh "tar -xf ${metadata.tarName}" dir("${metadata.dirName}") { try { - f + f() } finally { deleteDir() } From git at git.haskell.org Fri Jul 28 16:42:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:43 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (58697c9) Message-ID: <20170728164243.AFAB43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/58697c9e54bd6bc7370ca70340222c0b3d9feb03/ghc >--------------------------------------------------------------- commit 58697c9e54bd6bc7370ca70340222c0b3d9feb03 Author: Ben Gamari Date: Thu May 18 02:59:40 2017 -0400 Debug >--------------------------------------------------------------- 58697c9e54bd6bc7370ca70340222c0b3d9feb03 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 Fri Jul 28 16:42:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:46 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix FreeBSD architecture (0bc99ba) Message-ID: <20170728164246.6A3563A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0bc99ba94bef62ec4f028531e72a286037623e7a/ghc >--------------------------------------------------------------- commit 0bc99ba94bef62ec4f028531e72a286037623e7a Author: Ben Gamari Date: Mon May 29 13:55:03 2017 -0400 Fix FreeBSD architecture >--------------------------------------------------------------- 0bc99ba94bef62ec4f028531e72a286037623e7a 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 Fri Jul 28 16:42:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:49 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: More things (c7610fc) Message-ID: <20170728164249.270843A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c7610fc05fe58a4723bb847c0288250d4f6d2b64/ghc >--------------------------------------------------------------- commit c7610fc05fe58a4723bb847c0288250d4f6d2b64 Author: Ben Gamari Date: Thu May 18 01:38:55 2017 -0400 More things >--------------------------------------------------------------- c7610fc05fe58a4723bb847c0288250d4f6d2b64 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 Fri Jul 28 16:42:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:52 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Testing simpler Jenkinsfile (bdbfe5a) Message-ID: <20170728164252.6621A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/bdbfe5a67c3d304331f002bd6255275781949a3b/ghc >--------------------------------------------------------------- commit bdbfe5a67c3d304331f002bd6255275781949a3b Author: Ben Gamari Date: Fri Apr 21 14:29:34 2017 -0400 Testing simpler Jenkinsfile >--------------------------------------------------------------- bdbfe5a67c3d304331f002bd6255275781949a3b 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 Fri Jul 28 16:42:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:55 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Clean up treatment of tests (56f02d2) Message-ID: <20170728164255.1FF523A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/56f02d257a239b0bb970f05d2847b21b67f03fa6/ghc >--------------------------------------------------------------- commit 56f02d257a239b0bb970f05d2847b21b67f03fa6 Author: Ben Gamari Date: Tue May 30 01:10:56 2017 -0400 Clean up treatment of tests >--------------------------------------------------------------- 56f02d257a239b0bb970f05d2847b21b67f03fa6 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 Fri Jul 28 16:42:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:42:57 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Disable large address space on FreeBSD (d41b0f4) Message-ID: <20170728164257.D2B913A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d41b0f4bc5a57899b9d8b7921826e18369427653/ghc >--------------------------------------------------------------- commit d41b0f4bc5a57899b9d8b7921826e18369427653 Author: Ben Gamari Date: Mon May 29 16:34:26 2017 -0400 Disable large address space on FreeBSD >--------------------------------------------------------------- d41b0f4bc5a57899b9d8b7921826e18369427653 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 Fri Jul 28 16:43:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:00 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Checkout (2b2bd0c) Message-ID: <20170728164300.8BBFF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2b2bd0cb18208f8a5827f821b9ed626bbef1f764/ghc >--------------------------------------------------------------- commit 2b2bd0cb18208f8a5827f821b9ed626bbef1f764 Author: Ben Gamari Date: Thu May 18 01:19:52 2017 -0400 Checkout >--------------------------------------------------------------- 2b2bd0cb18208f8a5827f821b9ed626bbef1f764 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 Fri Jul 28 16:43:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:03 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Try again (6577110) Message-ID: <20170728164303.464023A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/65771107eab2b5fcdf2a820dbdb110cba3e4e54e/ghc >--------------------------------------------------------------- commit 65771107eab2b5fcdf2a820dbdb110cba3e4e54e Author: Ben Gamari Date: Mon May 29 16:42:42 2017 -0400 Try again >--------------------------------------------------------------- 65771107eab2b5fcdf2a820dbdb110cba3e4e54e 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 Fri Jul 28 16:43:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:06 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Reformat (b16f31b) Message-ID: <20170728164306.036113A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/b16f31b470ecdd5c117167c3224a17057a2dc46c/ghc >--------------------------------------------------------------- commit b16f31b470ecdd5c117167c3224a17057a2dc46c Author: Ben Gamari Date: Thu May 18 02:58:05 2017 -0400 Reformat >--------------------------------------------------------------- b16f31b470ecdd5c117167c3224a17057a2dc46c 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 Fri Jul 28 16:43:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:08 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Trim whitespace from git output (af80cfb) Message-ID: <20170728164308.B3F243A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/af80cfb185e61cefd9cd6347ae04bc83802692b0/ghc >--------------------------------------------------------------- commit af80cfb185e61cefd9cd6347ae04bc83802692b0 Author: Ben Gamari Date: Sun Jun 4 11:00:28 2017 -0400 Trim whitespace from git output >--------------------------------------------------------------- af80cfb185e61cefd9cd6347ae04bc83802692b0 Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 410a86d..b709774 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -279,7 +279,7 @@ def testGhc(params) { } def resolveCommitSha(String ref) { - return sh(script: "git rev-parse ${ref}", returnStdout: true) + return sh(script: "git rev-parse ${ref}", returnStdout: true).trim() } // Push update to ghc.readthedocs.org. From git at git.haskell.org Fri Jul 28 16:43:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:11 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix source directory name (94e5ef3) Message-ID: <20170728164311.6E7373A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/94e5ef356f579d019afb146cd452f66fadc00349/ghc >--------------------------------------------------------------- commit 94e5ef356f579d019afb146cd452f66fadc00349 Author: Ben Gamari Date: Sun Jun 4 11:06:15 2017 -0400 Fix source directory name >--------------------------------------------------------------- 94e5ef356f579d019afb146cd452f66fadc00349 Jenkinsfile | 11 +++++++++-- 1 file changed, 9 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index b709774..59daa63 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -40,7 +40,12 @@ stage("Build source distribution") { sh "mv sdistprep/ghc-${version}-src.tar.xz ghc-src.tar.xz" sh "mv sdistprep/ghc-${version}-testsuite.tar.xz ghc-testsuite.tar.xz" sh "mv sdistprep/ghc-${version}-windows-extra-src.tar.xz ghc-win32-tarballs.tar.xz" - stash(name: 'source-dist', includes: 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz') + + def json = new JSONObject() + json.put('dirName', "ghc-${version}") + writeJSON(file: 'src-dist.json', json: json) + + stash(name: 'source-dist', includes: 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz,src-dist.json') stash(name: 'testsuite-dist', includes: 'ghc-testsuite.tar.xz') } } @@ -216,7 +221,9 @@ def withGhcSrcDist(Closure f) { sh 'tar -xf ghc-src.tar.xz' sh 'tar -xf ghc-win32-tarballs.tar.xz' } - dir('ghc-*') { + + def metadata = readJSON file: 'src-dist.json' + dir(metadata.dirName) { f() } } From git at git.haskell.org Fri Jul 28 16:43:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:14 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Run jobs in parallel (d55eb06) Message-ID: <20170728164314.495313A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d55eb068a134413e56d5359b5efd3d2eaa001463/ghc >--------------------------------------------------------------- commit d55eb068a134413e56d5359b5efd3d2eaa001463 Author: Ben Gamari Date: Wed May 17 23:34:37 2017 -0400 Run jobs in parallel >--------------------------------------------------------------- d55eb068a134413e56d5359b5efd3d2eaa001463 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 Fri Jul 28 16:43:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:17 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix configure arguments (01a1446) Message-ID: <20170728164317.0B5053A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/01a144604ead6597e06df533b19c1e911f91faf5/ghc >--------------------------------------------------------------- commit 01a144604ead6597e06df533b19c1e911f91faf5 Author: Ben Gamari Date: Mon May 29 22:55:51 2017 -0400 Fix configure arguments >--------------------------------------------------------------- 01a144604ead6597e06df533b19c1e911f91faf5 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 Fri Jul 28 16:43:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:19 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Move to scripted pipeline (11ba0d1) Message-ID: <20170728164319.BB7C83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/11ba0d10d29e37d4b1ffb78bab7887e215b2c696/ghc >--------------------------------------------------------------- commit 11ba0d10d29e37d4b1ffb78bab7887e215b2c696 Author: Ben Gamari Date: Wed May 17 20:52:58 2017 -0400 Move to scripted pipeline >--------------------------------------------------------------- 11ba0d10d29e37d4b1ffb78bab7887e215b2c696 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 Fri Jul 28 16:43:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:22 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Don't run nofib on Windows (d39084f) Message-ID: <20170728164322.79D063A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d39084f2e8689307a638f328a6207a4cdc5be752/ghc >--------------------------------------------------------------- commit d39084f2e8689307a638f328a6207a4cdc5be752 Author: Ben Gamari Date: Mon May 29 16:14:11 2017 -0400 Don't run nofib on Windows >--------------------------------------------------------------- d39084f2e8689307a638f328a6207a4cdc5be752 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 Fri Jul 28 16:43:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:25 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (818dd89) Message-ID: <20170728164325.3B1E33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/818dd8949b86e7d31d1c8ff2a85fe23c76d684be/ghc >--------------------------------------------------------------- commit 818dd8949b86e7d31d1c8ff2a85fe23c76d684be Author: Ben Gamari Date: Wed May 31 14:57:34 2017 -0400 Debug >--------------------------------------------------------------- 818dd8949b86e7d31d1c8ff2a85fe23c76d684be 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 Fri Jul 28 16:43:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:27 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix Windows PATHs (82e206b) Message-ID: <20170728164327.EA6483A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/82e206ba598770c4c221adb10599066cd519fd30/ghc >--------------------------------------------------------------- commit 82e206ba598770c4c221adb10599066cd519fd30 Author: Ben Gamari Date: Mon May 29 16:31:28 2017 -0400 Fix Windows PATHs >--------------------------------------------------------------- 82e206ba598770c4c221adb10599066cd519fd30 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 Fri Jul 28 16:43:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:30 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Hopefully fix Windows (24ba01b) Message-ID: <20170728164330.A5E003A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/24ba01b3b7a1adbe44aa556b0f6f7df56ea2db94/ghc >--------------------------------------------------------------- commit 24ba01b3b7a1adbe44aa556b0f6f7df56ea2db94 Author: Ben Gamari Date: Mon May 29 22:33:46 2017 -0400 Hopefully fix Windows >--------------------------------------------------------------- 24ba01b3b7a1adbe44aa556b0f6f7df56ea2db94 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 Fri Jul 28 16:43:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:33 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add nofib, bindist, and aarch64 support (c4f5c04) Message-ID: <20170728164333.60A213A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c4f5c04e7701c6a49ca4e9dae026284531dda7ba/ghc >--------------------------------------------------------------- commit c4f5c04e7701c6a49ca4e9dae026284531dda7ba Author: Ben Gamari Date: Wed May 17 22:41:02 2017 -0400 Add nofib, bindist, and aarch64 support >--------------------------------------------------------------- c4f5c04e7701c6a49ca4e9dae026284531dda7ba 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 Fri Jul 28 16:43:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:36 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: No need to boot (da09987) Message-ID: <20170728164336.1E9713A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/da099870836b83c98ebf8f348e967db1fcd7d360/ghc >--------------------------------------------------------------- commit da099870836b83c98ebf8f348e967db1fcd7d360 Author: Ben Gamari Date: Sun Jun 4 10:54:49 2017 -0400 No need to boot >--------------------------------------------------------------- da099870836b83c98ebf8f348e967db1fcd7d360 Jenkinsfile | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index b7c9db5..410a86d 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -29,7 +29,10 @@ stage("Build source distribution") { """ } stage("Configuring tree") { - sh "./configure" + sh """ + ./boot + ./configure + """ } stage("Build tarballs") { def version = getMakeValue('make', 'ProjectVersion') @@ -162,10 +165,7 @@ def buildGhc(params) { if (unreg) { configure_opts += '--enable-unregisterised' } - sh """ - ./boot - ./configure ${configure_opts.join(' ')} - """ + sh "./configure ${configure_opts.join(' ')}" } stage('Build') { From git at git.haskell.org Fri Jul 28 16:43:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:38 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix test (ffbc83e) Message-ID: <20170728164338.D23043A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ffbc83e96441daee831593393fcfe7eb3e9f5e44/ghc >--------------------------------------------------------------- commit ffbc83e96441daee831593393fcfe7eb3e9f5e44 Author: Ben Gamari Date: Tue May 30 13:57:23 2017 -0400 Fix test >--------------------------------------------------------------- ffbc83e96441daee831593393fcfe7eb3e9f5e44 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 Fri Jul 28 16:43:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:41 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix documentation (4c81833) Message-ID: <20170728164341.914C73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/4c81833b7ddb7590dca3b3ee48f18977820c85dd/ghc >--------------------------------------------------------------- commit 4c81833b7ddb7590dca3b3ee48f18977820c85dd Author: Ben Gamari Date: Tue May 30 10:45:52 2017 -0400 Fix documentation >--------------------------------------------------------------- 4c81833b7ddb7590dca3b3ee48f18977820c85dd 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 Fri Jul 28 16:43:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:44 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: No need to configure (59bafb9) Message-ID: <20170728164344.4A4DF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/59bafb9b0ae1b90422cf54a59f10cc14be225e17/ghc >--------------------------------------------------------------- commit 59bafb9b0ae1b90422cf54a59f10cc14be225e17 Author: Ben Gamari Date: Sun Jun 4 10:47:30 2017 -0400 No need to configure >--------------------------------------------------------------- 59bafb9b0ae1b90422cf54a59f10cc14be225e17 Jenkinsfile | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index d2f39f3..6615265 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -29,10 +29,7 @@ stage("Build source distribution") { """ } stage("Configuring tree") { - sh """ - ./boot - ./configure - """ + sh "./configure" } stage("Build tarballs") { def version = getMakeValue('make', 'ProjectVersion') From git at git.haskell.org Fri Jul 28 16:43:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:47 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring (7679cad) Message-ID: <20170728164347.0BF843A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7679cad5b603c6228a920187499930a10f21ee4e/ghc >--------------------------------------------------------------- commit 7679cad5b603c6228a920187499930a10f21ee4e Author: Ben Gamari Date: Wed May 17 20:20:55 2017 -0400 Refactoring >--------------------------------------------------------------- 7679cad5b603c6228a920187499930a10f21ee4e 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 Fri Jul 28 16:43:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:49 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rework handling of Windows (fe64160) Message-ID: <20170728164349.B71E73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/fe6416066e18ed298655ce1867396bc25f910163/ghc >--------------------------------------------------------------- commit fe6416066e18ed298655ce1867396bc25f910163 Author: Ben Gamari Date: Mon May 29 13:08:49 2017 -0400 Rework handling of Windows >--------------------------------------------------------------- fe6416066e18ed298655ce1867396bc25f910163 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 Fri Jul 28 16:43:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:52 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Kill debugging (43c9aa6) Message-ID: <20170728164352.71C013A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/43c9aa6106de8056bf63fe3766e17416373fe1e8/ghc >--------------------------------------------------------------- commit 43c9aa6106de8056bf63fe3766e17416373fe1e8 Author: Ben Gamari Date: Thu May 18 01:39:32 2017 -0400 Kill debugging >--------------------------------------------------------------- 43c9aa6106de8056bf63fe3766e17416373fe1e8 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 Fri Jul 28 16:43:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:55 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: A bit more paranoia around directory deletion (3ce33d3) Message-ID: <20170728164355.3159C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/3ce33d36834ffecaafb9d09676c922ddbfbcc1cd/ghc >--------------------------------------------------------------- commit 3ce33d36834ffecaafb9d09676c922ddbfbcc1cd Author: Ben Gamari Date: Sun Jun 4 10:51:43 2017 -0400 A bit more paranoia around directory deletion It seems that the finally block never executes in some cases. Arg. >--------------------------------------------------------------- 3ce33d36834ffecaafb9d09676c922ddbfbcc1cd Jenkinsfile | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 6615265..b7c9db5 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -196,7 +196,10 @@ def getMakeValue(String makeCmd, String value) { } def withTempDir(String name, Closure f) { - sh "mkdir ${name}" + sh """ + rm -Rf ${name} || true + mkdir ${name} + """ dir(name) { try { f() From git at git.haskell.org Fri Jul 28 16:43:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:43:57 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix binding name (be4451c) Message-ID: <20170728164357.DFB253A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/be4451c06a09ce59b1f8afc86e04440ed0a209c8/ghc >--------------------------------------------------------------- commit be4451c06a09ce59b1f8afc86e04440ed0a209c8 Author: Ben Gamari Date: Mon Jun 12 22:25:11 2017 -0400 Fix binding name >--------------------------------------------------------------- be4451c06a09ce59b1f8afc86e04440ed0a209c8 Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 9f87698..24810c5 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -272,7 +272,7 @@ def testGhc(params) { withGhcBinDist(targetTriple) { stage('Configure') { - sh "./configure --prefix=\"`pwd`/${inst_dir}\"" + sh "./configure --prefix=\"`pwd`/${instDir}\"" sh "${makeCmd} install" } From git at git.haskell.org Fri Jul 28 16:44:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:00 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rework handling of nofib (b51912f) Message-ID: <20170728164400.986FC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/b51912fa7c979eb9b88dfc58c50d0a471662b52b/ghc >--------------------------------------------------------------- commit b51912fa7c979eb9b88dfc58c50d0a471662b52b Author: Ben Gamari Date: Mon Jun 5 13:32:37 2017 -0400 Rework handling of nofib Given that we want the measurements to be stable it makes sense to do these on a separate, quiet machine. >--------------------------------------------------------------- b51912fa7c979eb9b88dfc58c50d0a471662b52b Jenkinsfile | 32 +++++++++++++++++++++----------- 1 file changed, 21 insertions(+), 11 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 6fc89ae..adf8058 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -96,6 +96,13 @@ parallel ( */ ) +if (params.runNofib) { + node(label: 'linux && amd64 && perf') { + nofib(targetTriple: 'x86_64-linux-gnu') + } +} + + def withMingw(String msystem, Closure f) { // Derived from msys2's /etc/msystem def msysRoot = 'C:\\msys64' @@ -252,7 +259,6 @@ def withGhcBinDist(String targetTriple, Closure f) { def testGhc(params) { String targetTriple = params?.targetTriple String makeCmd = params?.makeCmd ?: 'make' - boolean runNofib = params?.runNofib withGhcBinDist(targetTriple) { stage('Configure') { @@ -276,18 +282,22 @@ def testGhc(params) { sh "${makeCmd} -Ctestsuite/tests stage=2 LOCAL=0 BINDIST=YES THREADS=${env.THREADS} ${target}" sh "${makeCmd} -Ctestsuite/tests/stage1 stage=1 LOCAL=0 BINDIST=YES THREADS=${env.THREADS} ${target}" } + } +} +def nofib(params) { + String targetTriple = params?.targetTriple + String makeCmd = params?.makeCmd ?: 'make' + withGhcBinDist(targetTriple) { stage('Run nofib') { - if (runNofib) { - installPkgs(['regex-compat']) - sh """ - cd nofib - ${makeCmd} clean - ${makeCmd} boot - ${makeCmd} >../nofib.log 2>&1 - """ - archiveArtifacts artifacts: 'nofib.log' - } + installPkgs(['regex-compat']) + sh """ + cd nofib + ${makeCmd} clean + ${makeCmd} boot + ${makeCmd} >../nofib.log 2>&1 + """ + archiveArtifacts artifacts: 'nofib.log' } } } From git at git.haskell.org Fri Jul 28 16:44:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:03 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Handle testsuite on Windows (5e6c4ba) Message-ID: <20170728164403.548883A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/5e6c4ba7b64d5950851f7b7f09fc8d392cadd040/ghc >--------------------------------------------------------------- commit 5e6c4ba7b64d5950851f7b7f09fc8d392cadd040 Author: Ben Gamari Date: Sat Jun 17 22:53:30 2017 -0400 Handle testsuite on Windows >--------------------------------------------------------------- 5e6c4ba7b64d5950851f7b7f09fc8d392cadd040 Jenkinsfile | 11 ++++++++--- 1 file changed, 8 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 179421e..b754745 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -265,16 +265,21 @@ def withGhcBinDist(String targetTriple, Closure f) { def testGhc(params) { String targetTriple = params?.targetTriple // See Note [Spaces in TEST_HC] - String instDir="bindisttest/install dir" String testGhc="${instDir}/bin/ghc" String makeCmd = params?.makeCmd ?: 'make' + String instDir="${pwd()}/bindisttest/install dir" withGhcBinDist(targetTriple) { stage('Configure') { echo 'echo $PATH' sh "which ghc" - sh "./configure --prefix=\"`pwd`/${instDir}\"" - sh "${makeCmd} install" + if (isUnix()) { + sh "./configure --prefix=\"${instDir}\"" + sh "${makeCmd} install" + } else { + sh "mkdir -p \"${instDir}\"" + sh "cp -R * ${instDir}" + } } stage('Install testsuite dependencies') { From git at git.haskell.org Fri Jul 28 16:44:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:06 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Archive source distribution (d39eeb3) Message-ID: <20170728164406.147A93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d39eeb3d111747fea8103ff8678b93250ad43d28/ghc >--------------------------------------------------------------- commit d39eeb3d111747fea8103ff8678b93250ad43d28 Author: Ben Gamari Date: Mon Jun 12 13:34:52 2017 -0400 Archive source distribution >--------------------------------------------------------------- d39eeb3d111747fea8103ff8678b93250ad43d28 Jenkinsfile | 14 ++++++++++---- 1 file changed, 10 insertions(+), 4 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index acaf373..9c2123d 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -48,8 +48,11 @@ stage("Build source distribution") { json.put('commit', resolveCommitSha('HEAD')) writeJSON(file: 'src-dist.json', json: json) - stash(name: 'source-dist', includes: 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz,src-dist.json') + def src_dist_files = 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz,src-dist.json' + stash(name: 'source-dist', includes: src_dist_files) stash(name: 'testsuite-dist', includes: 'ghc-testsuite.tar.xz') + archiveArtifacts artifacts: src_dist_files + archiveArtifacts artifacts: 'ghc-testsuite.tar.xz' } } } @@ -261,11 +264,15 @@ def withGhcBinDist(String targetTriple, Closure f) { def testGhc(params) { String targetTriple = params?.targetTriple + // See Note [Spaces in TEST_HC] + String instDir="bindisttest/install dir" + String testGhc="${instDir}/bin/ghc" String makeCmd = params?.makeCmd ?: 'make' withGhcBinDist(targetTriple) { stage('Configure') { - sh './configure' + sh "./configure --prefix=\"`pwd`/${inst_dir}\"" + sh "${makeCmd} install" } stage('Install testsuite dependencies') { @@ -282,8 +289,7 @@ def testGhc(params) { if (params.nightly) { target = 'slowtest' } - sh "${makeCmd} -Ctestsuite/tests stage=2 LOCAL=0 BINDIST=YES THREADS=${env.THREADS} ${target}" - sh "${makeCmd} -Ctestsuite/tests/stage1 stage=1 LOCAL=0 BINDIST=YES THREADS=${env.THREADS} ${target}" + sh "${makeCmd} -Ctestsuite/tests LOCAL=0 BINDIST=YES THREADS=${env.THREADS} TEST_HC=\"`pwd`/${testGhc}\" ${target}" } } } From git at git.haskell.org Fri Jul 28 16:44:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:08 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Ensure HOME is expanded (7cd7608) Message-ID: <20170728164408.C31CC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7cd7608500de0f5c1f22a8fac4244e1075a6a373/ghc >--------------------------------------------------------------- commit 7cd7608500de0f5c1f22a8fac4244e1075a6a373 Author: Ben Gamari Date: Sun Jun 18 16:35:12 2017 -0400 Ensure HOME is expanded >--------------------------------------------------------------- 7cd7608500de0f5c1f22a8fac4244e1075a6a373 Jenkinsfile | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index d559f06..9aac44f 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -111,14 +111,15 @@ def withMingw(String msystem, Closure f) { // Derived from msys2's /etc/msystem def msysRoot = 'C:\\msys64' String carch, prefix, ghcPath + home = sh(script: 'echo $HOME', returnStdout: true) if (msystem == 'MINGW32') { prefix = "${msysRoot}\\mingw32" carch = 'i686' - ghcPath = '$HOME/ghc-8.0.1-i386/bin' + ghcPath = "${home}/ghc-8.0.1-i386/bin" } else if (msystem == 'MINGW64') { prefix = "${msysRoot}\\mingw64" carch = 'x86_64' - ghcPath = '$HOME/ghc-8.0.2-x86_64/bin' + ghcPath = "${home}/ghc-8.0.2-x86_64/bin" } else { fail } From git at git.haskell.org Fri Jul 28 16:44:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:11 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Ensure that carch, prefix, and ghcPath are in scope (c214489) Message-ID: <20170728164411.7B3BF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c214489bad8f64cf28bd7bd6406725fb204b6f95/ghc >--------------------------------------------------------------- commit c214489bad8f64cf28bd7bd6406725fb204b6f95 Author: Ben Gamari Date: Mon Jun 12 16:31:31 2017 -0400 Ensure that carch, prefix, and ghcPath are in scope >--------------------------------------------------------------- c214489bad8f64cf28bd7bd6406725fb204b6f95 Jenkinsfile | 1 + 1 file changed, 1 insertion(+) diff --git a/Jenkinsfile b/Jenkinsfile index 9c2123d..98e0946 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -110,6 +110,7 @@ if (params.runNofib) { def withMingw(String msystem, Closure f) { // Derived from msys2's /etc/msystem def msysRoot = 'C:\\msys64' + String carch, prefix, ghcPath if (msystem == 'MINGW32') { prefix = "${msysRoot}\\mingw32" carch = 'i686' From git at git.haskell.org Fri Jul 28 16:44:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:14 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: No trailing newline (57ae63c) Message-ID: <20170728164414.3A9BC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/57ae63ca64aa0822b4de548345c657f7180dee25/ghc >--------------------------------------------------------------- commit 57ae63ca64aa0822b4de548345c657f7180dee25 Author: Ben Gamari Date: Mon Jun 19 07:27:07 2017 -0400 No trailing newline >--------------------------------------------------------------- 57ae63ca64aa0822b4de548345c657f7180dee25 Jenkinsfile | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 9aac44f..a808fcd 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -83,11 +83,13 @@ parallel ( } }, // Requires cygpath plugin? + /* "windows 64" : { node(label: 'windows && amd64') { withMingw('MINGW64') { buildAndTestGhc(targetTriple: 'x86_64-w64-mingw32') } } }, + */ "windows 32" : { node(label: 'windows && amd64') { withMingw('MINGW32') { buildAndTestGhc(targetTriple: 'x86_64-pc-msys') } @@ -109,9 +111,9 @@ if (params.runNofib) { def withMingw(String msystem, Closure f) { // Derived from msys2's /etc/msystem - def msysRoot = 'C:\\msys64' + String msysRoot = 'C:\\msys64' String carch, prefix, ghcPath - home = sh(script: 'echo $HOME', returnStdout: true) + home = sh(script: 'echo -n $HOME', returnStdout: true) if (msystem == 'MINGW32') { prefix = "${msysRoot}\\mingw32" carch = 'i686' From git at git.haskell.org Fri Jul 28 16:44:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:16 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Enable win64 again (2c7fbc9) Message-ID: <20170728164416.EC9123A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2c7fbc9811d3d613d2995549916aefa998a39984/ghc >--------------------------------------------------------------- commit 2c7fbc9811d3d613d2995549916aefa998a39984 Author: Ben Gamari Date: Mon Jun 19 12:39:58 2017 -0400 Enable win64 again >--------------------------------------------------------------- 2c7fbc9811d3d613d2995549916aefa998a39984 Jenkinsfile | 2 -- 1 file changed, 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index a808fcd..bcf3faa 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -83,13 +83,11 @@ parallel ( } }, // Requires cygpath plugin? - /* "windows 64" : { node(label: 'windows && amd64') { withMingw('MINGW64') { buildAndTestGhc(targetTriple: 'x86_64-w64-mingw32') } } }, - */ "windows 32" : { node(label: 'windows && amd64') { withMingw('MINGW32') { buildAndTestGhc(targetTriple: 'x86_64-pc-msys') } From git at git.haskell.org Fri Jul 28 16:44:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:19 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Various accumulated fixes (df71ba4) Message-ID: <20170728164419.A74CB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/df71ba45fb0a4813f768cf666282c0d9961038db/ghc >--------------------------------------------------------------- commit df71ba45fb0a4813f768cf666282c0d9961038db Author: Ben Gamari Date: Tue Jun 27 17:31:58 2017 -0400 Various accumulated fixes >--------------------------------------------------------------- df71ba45fb0a4813f768cf666282c0d9961038db Jenkinsfile | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index bcf3faa..fee5743 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -6,6 +6,10 @@ Linux (Debian) worker dependencies: * xutil-dev curl automake autoconf libtool python3 python3-sphinx, llvm-4.0 + + Requires approvals for: + * new net.sf.json.JSONObject + */ import net.sf.json.JSONObject @@ -123,7 +127,7 @@ def withMingw(String msystem, Closure f) { } else { fail } - chost = "${carch}-w64-mingw32" + String chost = "${carch}-w64-mingw32" withEnv(["MSYSTEM=${msystem}", "PATH+mingw=${prefix}\\bin", @@ -133,7 +137,7 @@ def withMingw(String msystem, Closure f) { "MSYSTEM_CHOST=${chost}", "MINGW_CHOST=${chost}", "MINGW_PREFIX=${prefix}", - "MINGW_PACKAGE_PREFIX=mingw-w64-${MSYSTEM_CARCH}", + "MINGW_PACKAGE_PREFIX=mingw-w64-${carch}", "CONFIG_SITE=${prefix}/etc/config.site" ], f) } @@ -202,7 +206,7 @@ def buildGhc(params) { sh "${makeCmd} binary-dist" def json = new JSONObject() def tarPath = getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') - def tarName = sh(script: "basename ${tarPath}", returnStdout: true) + def tarName = sh(script: "basename ${tarPath}", returnStdout: true).trim() json.put('tarName', tarName) json.put('dirName', getMakeValue(makeCmd, 'BIN_DIST_NAME')) json.put('ghcVersion', getMakeValue(makeCmd, 'ProjectVersion')) From git at git.haskell.org Fri Jul 28 16:44:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:22 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: debug win32 (c85db13) Message-ID: <20170728164422.62B083A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c85db1337be5fae66d024aa90bf21d2483e7b9bc/ghc >--------------------------------------------------------------- commit c85db1337be5fae66d024aa90bf21d2483e7b9bc Author: Ben Gamari Date: Sat Jun 17 23:34:18 2017 -0400 debug win32 >--------------------------------------------------------------- c85db1337be5fae66d024aa90bf21d2483e7b9bc Jenkinsfile | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index b754745..451a3a5 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -155,6 +155,9 @@ def buildGhc(params) { withGhcSrcDist() { stage('Configure') { + echo 'echo $PATH' + sh "which ghc" + def speed = 'NORMAL' if (params.nightly) { speed = 'SLOW' @@ -271,8 +274,6 @@ def testGhc(params) { withGhcBinDist(targetTriple) { stage('Configure') { - echo 'echo $PATH' - sh "which ghc" if (isUnix()) { sh "./configure --prefix=\"${instDir}\"" sh "${makeCmd} install" From git at git.haskell.org Fri Jul 28 16:44:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:25 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Don't try to record commit of bindist (6501234) Message-ID: <20170728164425.1EE4F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/6501234d6319e7c8339f5c019a9cedf9e9b09851/ghc >--------------------------------------------------------------- commit 6501234d6319e7c8339f5c019a9cedf9e9b09851 Author: Ben Gamari Date: Mon Jun 5 15:31:26 2017 -0400 Don't try to record commit of bindist >--------------------------------------------------------------- 6501234d6319e7c8339f5c019a9cedf9e9b09851 Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index adf8058..9a098e0 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -45,6 +45,7 @@ stage("Build source distribution") { def json = new JSONObject() json.put('dirName', "ghc-${version}" as String) + json.put('commit', resolveCommitSha('HEAD')) writeJSON(file: 'src-dist.json', json: json) stash(name: 'source-dist', includes: 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz,src-dist.json') @@ -191,7 +192,6 @@ def buildGhc(params) { def json = new JSONObject() def tarPath = getMakeValue(makeCmd, 'BIN_DIST_PREP_TAR_COMP') def tarName = sh(script: "basename ${tarPath}", returnStdout: true) - json.put('commit', resolveCommitSha('HEAD')) json.put('tarName', tarName) json.put('dirName', getMakeValue(makeCmd, 'BIN_DIST_NAME')) json.put('ghcVersion', getMakeValue(makeCmd, 'ProjectVersion')) From git at git.haskell.org Fri Jul 28 16:44:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:27 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Run stage1 tests as well (fd8c0d1) Message-ID: <20170728164427.CCB1A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/fd8c0d10a525af0b62ccf8067717ec4c40ab0ffc/ghc >--------------------------------------------------------------- commit fd8c0d10a525af0b62ccf8067717ec4c40ab0ffc Author: Ben Gamari Date: Sun Jun 4 21:24:15 2017 -0400 Run stage1 tests as well >--------------------------------------------------------------- fd8c0d10a525af0b62ccf8067717ec4c40ab0ffc Jenkinsfile | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index c369979..a051d7c 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -271,7 +271,8 @@ def testGhc(params) { if (params.nightly) { target = 'slowtest' } - sh "${makeCmd} THREADS=${env.THREADS} ${target}" + sh "${makeCmd} -Ctestsuite/tests stage=2 LOCAL=0 THREADS=${env.THREADS} ${target}" + sh "${makeCmd} -Ctestsuite/tests/stage1 stage=1 LOCAL=0 THREADS=${env.THREADS} ${target}" } stage('Run nofib') { From git at git.haskell.org Fri Jul 28 16:44:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:30 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix testGhc (2f65ae7) Message-ID: <20170728164430.878673A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2f65ae70291d48ac21ad201edd3ee4101b74f293/ghc >--------------------------------------------------------------- commit 2f65ae70291d48ac21ad201edd3ee4101b74f293 Author: Ben Gamari Date: Tue Jun 27 23:01:00 2017 -0400 Fix testGhc >--------------------------------------------------------------- 2f65ae70291d48ac21ad201edd3ee4101b74f293 Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 7f366d5..c135b9d 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -273,9 +273,9 @@ def withGhcBinDist(String targetTriple, Closure f) { def testGhc(params) { String targetTriple = params?.targetTriple // See Note [Spaces in TEST_HC] - String testGhc="${instDir}/bin/ghc" String makeCmd = params?.makeCmd ?: 'make' String instDir="${pwd()}/bindisttest/install dir" + String testGhc="${instDir}/bin/ghc" withGhcBinDist(targetTriple) { stage('Configure') { From git at git.haskell.org Fri Jul 28 16:44:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:33 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix GHC path (9f014c1) Message-ID: <20170728164433.4258A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9f014c1a4dc8e6aec9e733a5d2c6c81d1dcb50bc/ghc >--------------------------------------------------------------- commit 9f014c1a4dc8e6aec9e733a5d2c6c81d1dcb50bc Author: Ben Gamari Date: Tue Jun 13 00:44:15 2017 -0400 Fix GHC path >--------------------------------------------------------------- 9f014c1a4dc8e6aec9e733a5d2c6c81d1dcb50bc Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 24810c5..486e975 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -114,7 +114,7 @@ def withMingw(String msystem, Closure f) { if (msystem == 'MINGW32') { prefix = "${msysRoot}\\mingw32" carch = 'i686' - ghcPath = '$HOME/ghc-8.0.2-i386/bin' + ghcPath = '$HOME/ghc-8.0.1-i386/bin' } else if (msystem == 'MINGW64') { prefix = "${msysRoot}\\mingw64" carch = 'x86_64' From git at git.haskell.org Fri Jul 28 16:44:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:35 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix quoting of carch (643701b) Message-ID: <20170728164435.EE3983A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/643701ba1fcea6b5a4f1ec39a80124a4ebdae92e/ghc >--------------------------------------------------------------- commit 643701ba1fcea6b5a4f1ec39a80124a4ebdae92e Author: Ben Gamari Date: Mon Jun 12 16:40:33 2017 -0400 Fix quoting of carch >--------------------------------------------------------------- 643701ba1fcea6b5a4f1ec39a80124a4ebdae92e Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 98e0946..9f87698 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -122,7 +122,7 @@ def withMingw(String msystem, Closure f) { } else { fail } - chost = '${carch}-w64-mingw32' + chost = "${carch}-w64-mingw32" withEnv(["MSYSTEM=${msystem}", "PATH+mingw=${prefix}\\bin", From git at git.haskell.org Fri Jul 28 16:44:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:41 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Report JUnit results (9faa423) Message-ID: <20170728164441.65EA63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9faa4234e820ab56a9bf131dd82cba5ccaf87a88/ghc >--------------------------------------------------------------- commit 9faa4234e820ab56a9bf131dd82cba5ccaf87a88 Author: Ben Gamari Date: Thu Jul 27 22:44:46 2017 -0400 Report JUnit results >--------------------------------------------------------------- 9faa4234e820ab56a9bf131dd82cba5ccaf87a88 Jenkinsfile | 1 + 1 file changed, 1 insertion(+) diff --git a/Jenkinsfile b/Jenkinsfile index da5021f..ee6a884 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -303,6 +303,7 @@ def testGhc(params) { target = 'slowtest' } sh "${makeCmd} -Ctestsuite/tests LOCAL=0 BINDIST=YES THREADS=${env.THREADS} TEST_HC=\"${testGhc}\" ${target}" + junit 'testsuite*.xml' } } } From git at git.haskell.org Fri Jul 28 16:44:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:38 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix naming of crossCompiling (0d2c2cb) Message-ID: <20170728164438.A5BEA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0d2c2cb4a372cc988fc8672d987a6f0974dc63ab/ghc >--------------------------------------------------------------- commit 0d2c2cb4a372cc988fc8672d987a6f0974dc63ab Author: Ben Gamari Date: Wed Jul 12 17:01:16 2017 -0400 Fix naming of crossCompiling >--------------------------------------------------------------- 0d2c2cb4a372cc988fc8672d987a6f0974dc63ab Jenkinsfile | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index ec9e1d9..da5021f 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -72,10 +72,10 @@ parallel ( } }, "linux x86-64 -> aarch64 unreg" : { - node(label: 'linux && amd64') {buildAndTestGhc(cross: true, targetTriple: 'aarch64-linux-gnu', unreg: true)} + node(label: 'linux && amd64') {buildAndTestGhc(crossCompiling: true, targetTriple: 'aarch64-linux-gnu', unreg: true)} }, "linux x86-64 -> aarch64" : { - node(label: 'linux && amd64') {buildGhc(cross: true, targetTriple: 'aarch64-linux-gnu')} + node(label: 'linux && amd64') {buildGhc(crossCompiling: true, targetTriple: 'aarch64-linux-gnu')} node(label: 'linux && aarch64') {testGhc(targetTriple: 'aarch64-linux-gnu')} }, "aarch64" : { @@ -153,7 +153,7 @@ def buildAndTestGhc(params) { def buildGhc(params) { String targetTriple = params?.targetTriple - boolean cross = params?.crossTarget ?: false + boolean crossCompiling = params?.crossCompiling ?: false boolean unreg = params?.unreg ?: false boolean disableLargeAddrSpace = params?.disableLargeAddrSpace ?: false String makeCmd = params?.makeCmd ?: 'make' @@ -173,7 +173,7 @@ def buildGhc(params) { ValidateHpc=NO BUILD_DPH=NO """ - if (cross) { + if (crossCompiling) { build_mk += """ # Cross compiling HADDOCK_DOCS=NO @@ -186,7 +186,7 @@ def buildGhc(params) { writeFile(file: 'mk/build.mk', text: build_mk) def configure_opts = [] - if (cross) { + if (crossCompiling) { configure_opts += '--target=${targetTriple}' } if (disableLargeAddrSpace) { From git at git.haskell.org Fri Jul 28 16:44:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:44 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix windows paths (dabd2ad) Message-ID: <20170728164444.214EC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/dabd2ad0615a11c954f66e9dc6656a590806feea/ghc >--------------------------------------------------------------- commit dabd2ad0615a11c954f66e9dc6656a590806feea Author: Ben Gamari Date: Fri Jun 9 13:50:09 2017 -0400 Fix windows paths >--------------------------------------------------------------- dabd2ad0615a11c954f66e9dc6656a590806feea Jenkinsfile | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 9a098e0..acaf373 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -108,18 +108,21 @@ def withMingw(String msystem, Closure f) { // Derived from msys2's /etc/msystem def msysRoot = 'C:\\msys64' if (msystem == 'MINGW32') { - prefix = '${msysRoot}\\mingw32' + prefix = "${msysRoot}\\mingw32" carch = 'i686' + ghcPath = '$HOME/ghc-8.0.2-i386/bin' } else if (msystem == 'MINGW64') { - prefix = '${msysRoot}\\mingw64' + prefix = "${msysRoot}\\mingw64" carch = 'x86_64' + ghcPath = '$HOME/ghc-8.0.2-x86_64/bin' } 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", + "PATH+mingw=${prefix}\\bin", + "PATH+ghc=${ghcPath}", "MSYSTEM_PREFIX=${prefix}", "MSYSTEM_CARCH=${carch}", "MSYSTEM_CHOST=${chost}", From git at git.haskell.org Fri Jul 28 16:44:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:46 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix ghc path (e0f34bc) Message-ID: <20170728164446.CCCF73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/e0f34bc8eb103a44322cd8c82abf58b680f74117/ghc >--------------------------------------------------------------- commit e0f34bc8eb103a44322cd8c82abf58b680f74117 Author: Ben Gamari Date: Wed Jun 28 08:53:54 2017 -0400 Fix ghc path >--------------------------------------------------------------- e0f34bc8eb103a44322cd8c82abf58b680f74117 Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index c135b9d..b1b1d4d 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -302,7 +302,7 @@ def testGhc(params) { if (params.nightly) { target = 'slowtest' } - sh "${makeCmd} -Ctestsuite/tests LOCAL=0 BINDIST=YES THREADS=${env.THREADS} TEST_HC=\"`pwd`/${testGhc}\" ${target}" + sh "${makeCmd} -Ctestsuite/tests LOCAL=0 BINDIST=YES THREADS=${env.THREADS} TEST_HC=\"${testGhc}\" ${target}" } } } From git at git.haskell.org Fri Jul 28 16:44:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:49 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Kill debug output (202b673) Message-ID: <20170728164449.8845D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/202b673ef2d61862651e2754a42f9b9089444091/ghc >--------------------------------------------------------------- commit 202b673ef2d61862651e2754a42f9b9089444091 Author: Ben Gamari Date: Wed Jun 14 16:55:46 2017 -0400 Kill debug output >--------------------------------------------------------------- 202b673ef2d61862651e2754a42f9b9089444091 Jenkinsfile | 1 - 1 file changed, 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 1c6fa39..25ad7f1 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -239,7 +239,6 @@ def withGhcSrcDist(Closure f) { } def metadata = readJSON file: 'src-dist.json' - sh "cat src-dist.json" dir(metadata.dirName) { f() } From git at git.haskell.org Fri Jul 28 16:44:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:52 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Configure bindist (7883589) Message-ID: <20170728164452.438653A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7883589698b109dc9db661334a89b8a7c6772ec4/ghc >--------------------------------------------------------------- commit 7883589698b109dc9db661334a89b8a7c6772ec4 Author: Ben Gamari Date: Sun Jun 4 12:32:40 2017 -0400 Configure bindist >--------------------------------------------------------------- 7883589698b109dc9db661334a89b8a7c6772ec4 Jenkinsfile | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/Jenkinsfile b/Jenkinsfile index db32f78..c369979 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -253,6 +253,10 @@ def testGhc(params) { boolean runNofib = params?.runNofib withGhcBinDist(targetTriple) { + stage('Configure') { + sh './configure' + } + stage('Install testsuite dependencies') { if (params.nightly) { def pkgs = ['mtl', 'parallel', 'parsec', 'primitive', 'QuickCheck', From git at git.haskell.org Fri Jul 28 16:44:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:54 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: bindist: Compress with threaded xz by default (1724433) Message-ID: <20170728164454.F1F233A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/17244330fa3ed964a4229decdcc1ac3f1abfb91e/ghc >--------------------------------------------------------------- commit 17244330fa3ed964a4229decdcc1ac3f1abfb91e Author: Ben Gamari Date: Sun Jun 4 12:19:13 2017 -0400 bindist: Compress with threaded xz by default >--------------------------------------------------------------- 17244330fa3ed964a4229decdcc1ac3f1abfb91e mk/config.mk.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index 2e920ca..45e5587 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -795,7 +795,7 @@ else ifeq "$(TAR_COMP)" "gzip" TAR_COMP_CMD = $(GZIP_CMD) TAR_COMP_EXT = gz else ifeq "$(TAR_COMP)" "xz" -TAR_COMP_CMD = $(XZ_CMD) +TAR_COMP_CMD = $(XZ_CMD) --threads=0 TAR_COMP_EXT = xz else $(error $$(TAR_COMP) set to unknown value "$(TAR_COMP)" (supported: "bzip2", "gzip", "xz")) From git at git.haskell.org Fri Jul 28 16:44:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:44:57 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Show location of stage0 compiler (0ce0984) Message-ID: <20170728164457.B08F33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0ce0984c0a2fd1bacf1010c24b9bfcfbab1a9017/ghc >--------------------------------------------------------------- commit 0ce0984c0a2fd1bacf1010c24b9bfcfbab1a9017 Author: Ben Gamari Date: Tue Jun 13 16:10:23 2017 -0400 Show location of stage0 compiler >--------------------------------------------------------------- 0ce0984c0a2fd1bacf1010c24b9bfcfbab1a9017 Jenkinsfile | 1 + 1 file changed, 1 insertion(+) diff --git a/Jenkinsfile b/Jenkinsfile index 486e975..1c6fa39 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -272,6 +272,7 @@ def testGhc(params) { withGhcBinDist(targetTriple) { stage('Configure') { + sh "which ghc" sh "./configure --prefix=\"`pwd`/${instDir}\"" sh "${makeCmd} install" } From git at git.haskell.org Fri Jul 28 16:45:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:45:00 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Don't use deleteDir (8a32b6c) Message-ID: <20170728164500.6B3C93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/8a32b6c12362bf9b53e18fe8e9b5e10a01a680be/ghc >--------------------------------------------------------------- commit 8a32b6c12362bf9b53e18fe8e9b5e10a01a680be Author: Ben Gamari Date: Tue Jun 27 21:39:36 2017 -0400 Don't use deleteDir I suspect it is the reason that builds have been mysteriously failing despite all steps succeeding. >--------------------------------------------------------------- 8a32b6c12362bf9b53e18fe8e9b5e10a01a680be Jenkinsfile | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index fee5743..7f366d5 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -229,12 +229,12 @@ def withTempDir(String name, Closure f) { rm -Rf ${name} || true mkdir ${name} """ - dir(name) { - try { + try { + dir(name) { f() - } finally { - deleteDir() } + } finally { + sh "rm -Rf ${name}" } } @@ -260,12 +260,12 @@ def withGhcBinDist(String targetTriple, Closure f) { def metadata = readJSON file: "bindist.json" sh "tar -xf ${metadata.tarName}" sh "tar -xf ghc-testsuite.tar.xz" - dir(metadata.dirName) { - try { + try { + dir(metadata.dirName) { f() - } finally { - deleteDir() } + } finally { + sh "rm -R ${metadata.dirName}" } } } From git at git.haskell.org Fri Jul 28 16:45:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:45:03 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: debugging (9f4860a) Message-ID: <20170728164503.2612C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9f4860a685418132426389cda5a6d2af476331ab/ghc >--------------------------------------------------------------- commit 9f4860a685418132426389cda5a6d2af476331ab Author: Ben Gamari Date: Fri Jun 16 14:31:43 2017 -0400 debugging >--------------------------------------------------------------- 9f4860a685418132426389cda5a6d2af476331ab Jenkinsfile | 1 + 1 file changed, 1 insertion(+) diff --git a/Jenkinsfile b/Jenkinsfile index 25ad7f1..179421e 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -271,6 +271,7 @@ def testGhc(params) { withGhcBinDist(targetTriple) { stage('Configure') { + echo 'echo $PATH' sh "which ghc" sh "./configure --prefix=\"`pwd`/${instDir}\"" sh "${makeCmd} install" From git at git.haskell.org Fri Jul 28 16:45:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:45:05 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rip out debug output (9c85ca6) Message-ID: <20170728164505.DA7253A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9c85ca65b7f871aab8d99cde15129c53a6e07619/ghc >--------------------------------------------------------------- commit 9c85ca65b7f871aab8d99cde15129c53a6e07619 Author: Ben Gamari Date: Sun Jun 4 11:36:21 2017 -0400 Rip out debug output >--------------------------------------------------------------- 9c85ca65b7f871aab8d99cde15129c53a6e07619 Jenkinsfile | 4 ---- 1 file changed, 4 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 1f31e29..db32f78 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -43,7 +43,6 @@ stage("Build source distribution") { def json = new JSONObject() json.put('dirName', "ghc-${version}" as String) - echo "${json}" writeJSON(file: 'src-dist.json', json: json) stash(name: 'source-dist', includes: 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz,src-dist.json') @@ -225,8 +224,6 @@ def withGhcSrcDist(Closure f) { def metadata = readJSON file: 'src-dist.json' sh "cat src-dist.json" - echo "${metadata}" - sh "echo ${metadata.dirName}; ls ${metadata.dirName}" dir(metadata.dirName) { f() } @@ -238,7 +235,6 @@ def withGhcBinDist(String targetTriple, Closure f) { unstash "bindist-${targetTriple}" unstash "testsuite-dist" def metadata = readJSON file: "bindist.json" - echo "${metadata}" sh "tar -xf ${metadata.tarName}" sh "tar -xf ghc-testsuite.tar.xz" dir(metadata.dirName) { From git at git.haskell.org Fri Jul 28 16:45:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:45:08 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Properly quote instDir (8ff2492) Message-ID: <20170728164508.9F1B13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/8ff2492ad1b8df31bb09c48b48789a06035c33fc/ghc >--------------------------------------------------------------- commit 8ff2492ad1b8df31bb09c48b48789a06035c33fc Author: Ben Gamari Date: Thu Jun 29 08:58:04 2017 -0400 Properly quote instDir >--------------------------------------------------------------- 8ff2492ad1b8df31bb09c48b48789a06035c33fc Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index b1b1d4d..ab92bfe 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -284,7 +284,7 @@ def testGhc(params) { sh "${makeCmd} install" } else { sh "mkdir -p \"${instDir}\"" - sh "cp -R * ${instDir}" + sh "cp -R * \"${instDir}\"" } } From git at git.haskell.org Fri Jul 28 16:45:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:45:11 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Pass BINDIST to make test (537861a) Message-ID: <20170728164511.5B7303A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/537861a45f93d5e60fc352d896244de54f1b9ed4/ghc >--------------------------------------------------------------- commit 537861a45f93d5e60fc352d896244de54f1b9ed4 Author: Ben Gamari Date: Mon Jun 5 13:15:45 2017 -0400 Pass BINDIST to make test >--------------------------------------------------------------- 537861a45f93d5e60fc352d896244de54f1b9ed4 Jenkinsfile | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index a051d7c..7abcc9d 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,9 +1,11 @@ #!groovy /* - Dependencies: + Jenkins dependencies: * Pipeline Utility steps plugin + Linux (Debian) worker dependencies: + * xutil-dev curl automake autoconf libtool python3 python3-sphinx, llvm-4.0 */ import net.sf.json.JSONObject @@ -271,8 +273,8 @@ def testGhc(params) { if (params.nightly) { target = 'slowtest' } - sh "${makeCmd} -Ctestsuite/tests stage=2 LOCAL=0 THREADS=${env.THREADS} ${target}" - sh "${makeCmd} -Ctestsuite/tests/stage1 stage=1 LOCAL=0 THREADS=${env.THREADS} ${target}" + sh "${makeCmd} -Ctestsuite/tests stage=2 LOCAL=0 BINDIST=YES THREADS=${env.THREADS} ${target}" + sh "${makeCmd} -Ctestsuite/tests/stage1 stage=1 LOCAL=0 BINDIST=YES THREADS=${env.THREADS} ${target}" } stage('Run nofib') { From git at git.haskell.org Fri Jul 28 16:45:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:45:14 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Use named argument list (53fe1e5) Message-ID: <20170728164514.2738C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/53fe1e570be92e9f1eed03d7dd876a0193626e0c/ghc >--------------------------------------------------------------- commit 53fe1e570be92e9f1eed03d7dd876a0193626e0c Author: Ben Gamari Date: Mon Jun 5 13:27:27 2017 -0400 Use named argument list >--------------------------------------------------------------- 53fe1e570be92e9f1eed03d7dd876a0193626e0c Jenkinsfile | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 7abcc9d..6fc89ae 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -193,7 +193,7 @@ def buildGhc(params) { writeJSON(file: 'bindist.json', json: 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}" + archiveArtifacts artifacts: tarName } } } @@ -286,7 +286,7 @@ def testGhc(params) { ${makeCmd} boot ${makeCmd} >../nofib.log 2>&1 """ - archiveArtifacts 'nofib.log' + archiveArtifacts artifacts: 'nofib.log' } } } From git at git.haskell.org Fri Jul 28 16:45:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:45:16 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Preserve file attributes when copying bindist into place (816b385) Message-ID: <20170728164516.DE8F73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/816b385fcf62ac4c3bb90ceff960d6f86c6b04fc/ghc >--------------------------------------------------------------- commit 816b385fcf62ac4c3bb90ceff960d6f86c6b04fc Author: Ben Gamari Date: Sat Jul 8 15:20:39 2017 -0400 Preserve file attributes when copying bindist into place >--------------------------------------------------------------- 816b385fcf62ac4c3bb90ceff960d6f86c6b04fc Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index ab92bfe..ec9e1d9 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -284,7 +284,7 @@ def testGhc(params) { sh "${makeCmd} install" } else { sh "mkdir -p \"${instDir}\"" - sh "cp -R * \"${instDir}\"" + sh "cp -a * \"${instDir}\"" } } From git at git.haskell.org Fri Jul 28 16:45:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:45:19 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (4f993b7) Message-ID: <20170728164519.97A793A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/4f993b78e11fb4c3b8c744c6dd962b5ddaf3c1b1/ghc >--------------------------------------------------------------- commit 4f993b78e11fb4c3b8c744c6dd962b5ddaf3c1b1 Author: Ben Gamari Date: Sun Jun 4 11:32:08 2017 -0400 Debug >--------------------------------------------------------------- 4f993b78e11fb4c3b8c744c6dd962b5ddaf3c1b1 Jenkinsfile | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index bad87bf..1f31e29 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -42,7 +42,8 @@ stage("Build source distribution") { sh "mv sdistprep/ghc-${version}-windows-extra-src.tar.xz ghc-win32-tarballs.tar.xz" def json = new JSONObject() - json.put('dirName', "ghc-${version}") + json.put('dirName', "ghc-${version}" as String) + echo "${json}" writeJSON(file: 'src-dist.json', json: json) stash(name: 'source-dist', includes: 'ghc-src.tar.xz,ghc-win32-tarballs.tar.xz,src-dist.json') From git at git.haskell.org Fri Jul 28 16:45:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:45:22 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Ugh, sh not echo (fa2fbbf) Message-ID: <20170728164522.51EDB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/fa2fbbfb083ad365a15d36638cac14ffe90b1c21/ghc >--------------------------------------------------------------- commit fa2fbbfb083ad365a15d36638cac14ffe90b1c21 Author: Ben Gamari Date: Sun Jun 18 09:35:42 2017 -0400 Ugh, sh not echo >--------------------------------------------------------------- fa2fbbfb083ad365a15d36638cac14ffe90b1c21 Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 451a3a5..d559f06 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -155,7 +155,7 @@ def buildGhc(params) { withGhcSrcDist() { stage('Configure') { - echo 'echo $PATH' + sh 'echo $PATH' sh "which ghc" def speed = 'NORMAL' From git at git.haskell.org Fri Jul 28 16:45:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 16:45:25 +0000 (UTC) Subject: [commit: ghc] wip/jenkins's head updated: Report JUnit results (9faa423) Message-ID: <20170728164525.900513A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/jenkins' now includes: 6b77914 Fix instantiation of pattern synonyms af6d225 Remove redundant constraint in context b1317a3 Fix ASSERT failure in tc269 452755d Do not discard insolubles in implications ad0037e Add DebugCallStack to piResultTy d618649 Error eagerly after renaming failures in reifyInstances b3b564f Merge types and kinds in DsMeta 424ecad Add regression tests for #13601, #13780, #13877 5e940bd Switched out optparse for argparse in runtests.py 54d3a1f testsuite: Produce JUnit output 262bb95 testsuite: Add test for #14028 274e9b2 Add “BINARY_DIST_DIR” to Makefile dac4b9d ByteCodeGen: use byte indexing for BCenv 2974f81 Fix lld detection if both gold and lld are found bdbfe5a Testing simpler Jenkinsfile b693d6d Testing 0cf1486 Add THREADS parameter 7679cad Refactoring 11ba0d1 Move to scripted pipeline c4f5c04 Add nofib, bindist, and aarch64 support d55eb06 Run jobs in parallel 22a9b99 Debug 697490b Cross 2b2bd0c Checkout c7610fc More things 43c9aa6 Kill debugging 588d91c Unregisterised c96959f windows c580545 Refactoring, add Windows, fix cross 0513f72 Debug b16f31b Reformat 58697c9 Debug 770e7f9 Nailed the Windows issue fe64160 Rework handling of Windows 0bc99ba Fix FreeBSD architecture 270c9f2 Parametrize on make command 67f51b5 Use archiveArtifacts instead of archive 184f683 Debug d39084f Don't run nofib on Windows 82e206b Fix Windows PATHs d41b0f4 Disable large address space on FreeBSD 6577110 Try again d713c32 Hmm 0a51089 Disable non-Windows builds 24ba01b Hopefully fix Windows 03a0526 Reenable everything else 01a1446 Fix configure arguments 72a7915 Clean 56f02d2 Clean up treatment of tests 318a8e0 Handle documentation cd684e9 Fix tarball generation 4c81833 Fix documentation 7ec638a Fix testsuite ffbc83e Fix test e9fded2 Be more explicit b216799 Fix JSON serialization 381225c Fix missing binding 818dd89 Debug a758f59 More debugging fb37013 Fix tarName d9befc5 Actually call closure 55389c2 Build from source distribution fcf5edf Introduce echo! make target a09905f Fix tarball names 59bafb9 No need to configure 3ce33d3 A bit more paranoia around directory deletion da09987 No need to boot af80cfb Trim whitespace from git output 94e5ef3 Fix source directory name 1c6bb01 Debuggging c436d8c Debug 7d8cc05 Try adding type annotation 4f993b7 Debug 9c85ca6 Rip out debug output 1724433 bindist: Compress with threaded xz by default 7883589 Configure bindist fd8c0d1 Run stage1 tests as well 537861a Pass BINDIST to make test 53fe1e5 Use named argument list b51912f Rework handling of nofib 6501234 Don't try to record commit of bindist dabd2ad Fix windows paths d39eeb3 Archive source distribution c214489 Ensure that carch, prefix, and ghcPath are in scope 643701b Fix quoting of carch be4451c Fix binding name 9f014c1 Fix GHC path 0ce0984 Show location of stage0 compiler 202b673 Kill debug output 9f4860a debugging 5e6c4ba Handle testsuite on Windows c85db13 debug win32 fa2fbbf Ugh, sh not echo 7cd7608 Ensure HOME is expanded 57ae63c No trailing newline 2c7fbc9 Enable win64 again df71ba4 Various accumulated fixes 8a32b6c Don't use deleteDir 2f65ae7 Fix testGhc e0f34bc Fix ghc path 8ff2492 Properly quote instDir 816b385 Preserve file attributes when copying bindist into place 0d2c2cb Fix naming of crossCompiling 9faa423 Report JUnit results From git at git.haskell.org Fri Jul 28 17:31:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 17:31:54 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Delete hoopl submodule gitmodules entry (1fd86c8) Message-ID: <20170728173154.17E973A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/1fd86c86c1c969bca3d55b5aef30a0e6c284a0cd/ghc >--------------------------------------------------------------- commit 1fd86c86c1c969bca3d55b5aef30a0e6c284a0cd Author: Ben Gamari Date: Fri Jul 28 13:31:32 2017 -0400 Delete hoopl submodule gitmodules entry >--------------------------------------------------------------- 1fd86c86c1c969bca3d55b5aef30a0e6c284a0cd .gitmodules | 4 ---- 1 file changed, 4 deletions(-) diff --git a/.gitmodules b/.gitmodules index 55d360a..07ed3b7 100644 --- a/.gitmodules +++ b/.gitmodules @@ -70,10 +70,6 @@ path = libraries/filepath url = ../packages/filepath.git ignore = none -[submodule "libraries/hoopl"] - path = libraries/hoopl - url = ../packages/hoopl.git - ignore = none [submodule "libraries/hpc"] path = libraries/hpc url = ../packages/hpc.git From git at git.haskell.org Fri Jul 28 17:32:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 17:32:50 +0000 (UTC) Subject: [commit: ghc] master: gitmodules: Delete entry for dead hoopl submodule (f134bfb) Message-ID: <20170728173250.9B54C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f134bfb84d2e6ddb99f3ba008d8b156d3f454a46/ghc >--------------------------------------------------------------- commit f134bfb84d2e6ddb99f3ba008d8b156d3f454a46 Author: Ben Gamari Date: Fri Jul 28 13:32:19 2017 -0400 gitmodules: Delete entry for dead hoopl submodule >--------------------------------------------------------------- f134bfb84d2e6ddb99f3ba008d8b156d3f454a46 .gitmodules | 4 ---- 1 file changed, 4 deletions(-) diff --git a/.gitmodules b/.gitmodules index 55d360a..07ed3b7 100644 --- a/.gitmodules +++ b/.gitmodules @@ -70,10 +70,6 @@ path = libraries/filepath url = ../packages/filepath.git ignore = none -[submodule "libraries/hoopl"] - path = libraries/hoopl - url = ../packages/hoopl.git - ignore = none [submodule "libraries/hpc"] path = libraries/hpc url = ../packages/hpc.git From git at git.haskell.org Fri Jul 28 17:35:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 17:35:55 +0000 (UTC) Subject: [commit: ghc] master: configure: Ensure that user's LD setting is respected (d08b9cc) Message-ID: <20170728173555.B09393A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d08b9ccdf2812e8f8fa34d0c89275deee574524c/ghc >--------------------------------------------------------------- commit d08b9ccdf2812e8f8fa34d0c89275deee574524c Author: Ben Gamari Date: Fri Jul 28 13:35:01 2017 -0400 configure: Ensure that user's LD setting is respected This broke in the fix for #13541. >--------------------------------------------------------------- d08b9ccdf2812e8f8fa34d0c89275deee574524c aclocal.m4 | 1 + 1 file changed, 1 insertion(+) diff --git a/aclocal.m4 b/aclocal.m4 index 0389474..11606c7 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2283,6 +2283,7 @@ AC_DEFUN([FIND_LD],[ [enable_ld_override=yes]) if test "x$enable_ld_override" = "xyes"; then + TmpLd="$LD" # In case the user set LD AC_CHECK_TARGET_TOOLS([TmpLd], [ld.lld ld.gold ld]) out=`$TmpLd --version` From git at git.haskell.org Fri Jul 28 20:33:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 20:33:08 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Small changes to address Ben's comments (e04118d) Message-ID: <20170728203308.E8BCD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/e04118d15dd06471afda042bcb91a5f5947b0d14/ghc >--------------------------------------------------------------- commit e04118d15dd06471afda042bcb91a5f5947b0d14 Author: Jared Weakly Date: Tue Jul 18 17:35:34 2017 -0700 Small changes to address Ben's comments Signed-off-by: Jared Weakly >--------------------------------------------------------------- e04118d15dd06471afda042bcb91a5f5947b0d14 testsuite/driver/runtests.py | 13 +++++++++---- testsuite/driver/testglobals.py | 2 +- testsuite/driver/testlib.py | 5 ++--- testsuite/driver/testutil.py | 6 ++++-- 4 files changed, 16 insertions(+), 10 deletions(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index 239003c..e0c652a 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -54,9 +54,9 @@ long_options = [ "check-files-written", # check files aren't written by multiple tests "verbose=", # verbose (0,1,2 so far) "skip-perf-tests", # skip performance tests - "only-perf-tests", # Only do performance tests + "only-perf-tests", # Only do performance tests "use-git-notes", # use git notes to store metrics. NOTE: This is expected to become the default and will eventually be taken out. - "TEST_ENV=", # Override default chosen test-env. + "test-env=", # Override default chosen test-env. ] opts, args = getopt.getopt(sys.argv[1:], "e:", long_options) @@ -125,8 +125,8 @@ for opt,arg in opts: sys.exit(1) config.verbose = int(arg) - if opt == '--TEST_ENV': - config.TEST_ENV = arg + if opt == '--test-env': + config.test_env = arg config.cygwin = False @@ -338,6 +338,11 @@ else: summary(t, sys.stdout, config.no_print_summary) + # This here is loading up all of the git notes into memory. + # It's most likely in the wrong spot and I haven't fully fleshed out + # where exactly I'm putting this and how I'm refactoring the performance + # test running logic. + # Currently this is useful for debugging, at least. if config.use_git_notes: note = subprocess.check_output(["git","notes","--ref=perf","append","-m", "\n".join(config.accumulate_metrics)]) parse_git_notes('perf') # Should this be hardcoded? Most likely not... diff --git a/testsuite/driver/testglobals.py b/testsuite/driver/testglobals.py index bd8eefe..aa81b32 100644 --- a/testsuite/driver/testglobals.py +++ b/testsuite/driver/testglobals.py @@ -125,7 +125,7 @@ class TestConfig: # To accumulate the metrics for the git notes self.accumulate_metrics = [] # Has the user defined a custom test environment? Local is default. - self.TEST_ENV = 'local' + self.test_env = 'local' global config config = TestConfig() diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index a54fe38..a5a97fa 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1085,7 +1085,6 @@ def stats( name, way, stats_file ): # Check -t stats info def checkStats(name, way, stats_file, range_fields): - full_name = name + '(' + way + ')' result = passed() @@ -1111,8 +1110,8 @@ def checkStats(name, way, stats_file, range_fields): # Add val into the git note if option is set. if config.use_git_notes: - test_env = config.TEST_ENV - config.accumulate_metrics.append(test_env + '\t' + name + '\t' + way + '\t' + field + '\t' + str(val)) + test_env = config.test_env + config.accumulate_metrics.append('\t'.join([test_env, name, way, field, str(val)])) if val < lowerBound: print(field, 'value is too low:') diff --git a/testsuite/driver/testutil.py b/testsuite/driver/testutil.py index 59906a0..1fe1c20 100644 --- a/testsuite/driver/testutil.py +++ b/testsuite/driver/testutil.py @@ -54,8 +54,10 @@ def parse_git_notes(namespace): logFields = ['TEST_ENV','TEST','WAY','METRIC','VALUE'] log = subprocess.check_output(['git', 'notes', '--ref=' + namespace, 'show']).decode('utf-8') log = log.strip('\n').split('\n') - log = [entry.strip('\t').split('\t') for entry in log] - log = [dict(zip(logFields, row)) for row in log] + log = [line.strip('\t').split('\t') for line in log] + log = [dict(zip(logFields, field)) for field in log] + return log + # Add a print statement here if you want to see what's being loaded from git notes. # On Windows, os.symlink is not defined with Python 2.7, but is in Python 3 # when using msys2, as GHC does. Unfortunately, only Administrative users have From git at git.haskell.org Fri Jul 28 20:33:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 20:33:11 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Basic metrics collection and command line options working (83a482c) Message-ID: <20170728203311.AA6E93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/83a482c1ff87ef1655b2280cf6f67d83086ae266/ghc >--------------------------------------------------------------- commit 83a482c1ff87ef1655b2280cf6f67d83086ae266 Author: Jared Weakly Date: Thu Jul 6 17:16:49 2017 -0700 Basic metrics collection and command line options working >--------------------------------------------------------------- 83a482c1ff87ef1655b2280cf6f67d83086ae266 libraries/array | 2 +- libraries/hoopl | 1 + testsuite/driver/runtests.py | 36 ++++++++++++++++++++++++------------ testsuite/driver/testglobals.py | 11 ++++++++++- testsuite/driver/testlib.py | 6 ++++++ testsuite/driver/testutil.py | 4 ++++ testsuite/mk/test.mk | 12 ++++++++++++ 7 files changed, 58 insertions(+), 14 deletions(-) diff --git a/libraries/array b/libraries/array index 9a23fea..f7b69e9 160000 --- a/libraries/array +++ b/libraries/array @@ -1 +1 @@ -Subproject commit 9a23feac0b78e713c0f7877066fa24dbc2217c20 +Subproject commit f7b69e9cb914cb69bbede5264729523fb8669db1 diff --git a/libraries/hoopl b/libraries/hoopl new file mode 160000 index 0000000..ac24864 --- /dev/null +++ b/libraries/hoopl @@ -0,0 +1 @@ +Subproject commit ac24864c2db7951a6f34674e2b11b69d37ef84ff diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index 7e4f375..c09b063 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -42,18 +42,21 @@ def signal_handler(signal, frame): # cmd-line options long_options = [ - "configfile=", # config file - "config=", # config field - "rootdir=", # root of tree containing tests (default: .) - "summary-file=", # file in which to save the (human-readable) summary - "no-print-summary=", # should we print the summary? - "only=", # just this test (can be give multiple --only= flags) - "way=", # just this way - "skipway=", # skip this way - "threads=", # threads to run simultaneously - "check-files-written", # check files aren't written by multiple tests - "verbose=", # verbose (0,1,2 so far) - "skip-perf-tests", # skip performance tests + "configfile=", # config file + "config=", # config field + "rootdir=", # root of tree containing tests (default: .) + "summary-file=", # file in which to save the (human-readable) summary + "no-print-summary=", # should we print the summary? + "only=", # just this test (can be give multiple --only= flags) + "way=", # just this way + "skipway=", # skip this way + "threads=", # threads to run simultaneously + "check-files-written", # check files aren't written by multiple tests + "verbose=", # verbose (0,1,2 so far) + "skip-perf-tests", # skip performance tests + "only-perf-tests", # Only do performance tests + "use-git-notes", # use git notes to store metrics. NOTE: This is expected to become the default and will eventually be taken out. + "TEST_ENV=", # Override default chosen test-env. ] opts, args = getopt.getopt(sys.argv[1:], "e:", long_options) @@ -110,12 +113,21 @@ for opt,arg in opts: if opt == '--skip-perf-tests': config.skip_perf_tests = True + if opt == '--only-perf-tests': + config.only_perf_tests = True + + if opt == '--use-git-notes': + config.use_git_notes = True + if opt == '--verbose': if arg not in ["0","1","2","3","4","5"]: sys.stderr.write("ERROR: requested verbosity %s not supported, use 0,1,2,3,4 or 5" % arg) sys.exit(1) config.verbose = int(arg) + if opt == '--TEST_ENV': + config.TEST_ENV = arg + config.cygwin = False config.msys = False diff --git a/testsuite/driver/testglobals.py b/testsuite/driver/testglobals.py index fc050e6..bd8eefe 100644 --- a/testsuite/driver/testglobals.py +++ b/testsuite/driver/testglobals.py @@ -117,6 +117,16 @@ class TestConfig: # Should we skip performance tests self.skip_perf_tests = False + # Only do performance tests + self.only_perf_tests = False + + # Should we dump statistics to git notes? + self.use_git_notes = False + # To accumulate the metrics for the git notes + self.accumulate_metrics = [] + # Has the user defined a custom test environment? Local is default. + self.TEST_ENV = 'local' + global config config = TestConfig() @@ -283,4 +293,3 @@ default_testopts = TestOptions() # (bug, directory, name) of tests marked broken global brokens brokens = [] - diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 26e3d17..ae82d1f 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1084,6 +1084,7 @@ def stats( name, way, stats_file ): # Check -t stats info def checkStats(name, way, stats_file, range_fields): + full_name = name + '(' + way + ')' result = passed() @@ -1107,6 +1108,11 @@ def checkStats(name, way, stats_file, range_fields): deviation = round(((float(val) * 100)/ expected) - 100, 1) + # Add val into the git note if option is set. + if config.use_git_notes: + test_env = config.TEST_ENV + config.accumulate_metrics.append(test_env + '\t' + name + '\t' + way + '\t' + field + '\t' + str(val)) + if val < lowerBound: print(field, 'value is too low:') print('(If this is because you have improved GHC, please') diff --git a/testsuite/driver/testutil.py b/testsuite/driver/testutil.py index dcba177..c6297ff 100644 --- a/testsuite/driver/testutil.py +++ b/testsuite/driver/testutil.py @@ -47,6 +47,10 @@ def lndir(srcdir, dstdir): os.mkdir(dst) lndir(src, dst) +# def git_append(note): +# def print_metrics(): +# print(config.accumulate_metrics) + # On Windows, os.symlink is not defined with Python 2.7, but is in Python 3 # when using msys2, as GHC does. Unfortunately, only Administrative users have # the privileges necessary to create symbolic links by default. Consequently we diff --git a/testsuite/mk/test.mk b/testsuite/mk/test.mk index a44e200..9896883 100644 --- a/testsuite/mk/test.mk +++ b/testsuite/mk/test.mk @@ -195,6 +195,18 @@ ifeq "$(SKIP_PERF_TESTS)" "YES" RUNTEST_OPTS += --skip-perf-tests endif +ifeq "$(ONLY_PERF_TESTS)" "YES" +RUNTEST_OPTS += --only-perf-tests +endif + +ifeq "$(USE_GIT_NOTES)" "YES" +RUNTEST_OPTS += --use-git-notes +endif + +ifneq "$(TEST_ENV)" "" +RUNTEST_OPTS += --TEST_ENV="$(TEST_ENV)" +endif + ifeq "$(CLEANUP)" "0" RUNTEST_OPTS += -e config.cleanup=False else ifeq "$(CLEANUP)" "NO" From git at git.haskell.org Fri Jul 28 20:33:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 20:33:14 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: ONLY_PERF_TESTS=YES now fully implemented (b4a9820) Message-ID: <20170728203314.687C23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/b4a9820184bf579f28aa9864e5a6b29c81d40cdd/ghc >--------------------------------------------------------------- commit b4a9820184bf579f28aa9864e5a6b29c81d40cdd Author: Jared Weakly Date: Wed Jul 12 17:30:31 2017 -0700 ONLY_PERF_TESTS=YES now fully implemented >--------------------------------------------------------------- b4a9820184bf579f28aa9864e5a6b29c81d40cdd testsuite/driver/runtests.py | 2 ++ testsuite/driver/testlib.py | 1 + 2 files changed, 3 insertions(+) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index c09b063..996dae1 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -337,6 +337,8 @@ else: sys.stdout.flush() summary(t, sys.stdout, config.no_print_summary) + print("Only perf tests: " + str(config.only_perf_tests) + "\n") + print("Skip perf tests: " + str(config.skip_perf_tests) + "\n") if config.summary_file != '': with open(config.summary_file, 'w') as file: diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index ae82d1f..a54fe38 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -714,6 +714,7 @@ def test_common_work(watcher, name, opts, func, args): and (getTestOpts().only_ways == None or way in getTestOpts().only_ways) \ and (config.cmdline_ways == [] or way in config.cmdline_ways) \ and (not (config.skip_perf_tests and isStatsTest())) \ + and (not (config.only_perf_tests and (not isStatsTest()))) \ and way not in getTestOpts().omit_ways # Which ways we are asked to skip From git at git.haskell.org Fri Jul 28 20:33:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 20:33:17 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Can now load up git note data into python (df78afc) Message-ID: <20170728203317.269013A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/df78afc0d54f7513d855ea08e5bf56e579a2b143/ghc >--------------------------------------------------------------- commit df78afc0d54f7513d855ea08e5bf56e579a2b143 Author: Jared Weakly Date: Tue Jul 18 12:17:57 2017 -0700 Can now load up git note data into python >--------------------------------------------------------------- df78afc0d54f7513d855ea08e5bf56e579a2b143 testsuite/driver/runtests.py | 6 ++++-- testsuite/driver/testutil.py | 12 +++++++++--- 2 files changed, 13 insertions(+), 5 deletions(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index 996dae1..239003c 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -337,8 +337,10 @@ else: sys.stdout.flush() summary(t, sys.stdout, config.no_print_summary) - print("Only perf tests: " + str(config.only_perf_tests) + "\n") - print("Skip perf tests: " + str(config.skip_perf_tests) + "\n") + + if config.use_git_notes: + note = subprocess.check_output(["git","notes","--ref=perf","append","-m", "\n".join(config.accumulate_metrics)]) + parse_git_notes('perf') # Should this be hardcoded? Most likely not... if config.summary_file != '': with open(config.summary_file, 'w') as file: diff --git a/testsuite/driver/testutil.py b/testsuite/driver/testutil.py index c6297ff..59906a0 100644 --- a/testsuite/driver/testutil.py +++ b/testsuite/driver/testutil.py @@ -47,9 +47,15 @@ def lndir(srcdir, dstdir): os.mkdir(dst) lndir(src, dst) -# def git_append(note): -# def print_metrics(): -# print(config.accumulate_metrics) +# This function allows one to read in git notes from the commandline +# and then breaks it into a list of dictionaries that can be parsed +# later on in the testing functions. +def parse_git_notes(namespace): + logFields = ['TEST_ENV','TEST','WAY','METRIC','VALUE'] + log = subprocess.check_output(['git', 'notes', '--ref=' + namespace, 'show']).decode('utf-8') + log = log.strip('\n').split('\n') + log = [entry.strip('\t').split('\t') for entry in log] + log = [dict(zip(logFields, row)) for row in log] # On Windows, os.symlink is not defined with Python 2.7, but is in Python 3 # when using msys2, as GHC does. Unfortunately, only Administrative users have From git at git.haskell.org Fri Jul 28 20:33:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 20:33:19 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Basic metrics collection and command line options working (e793a24) Message-ID: <20170728203319.D86BE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/e793a24ec0a05f64e1916a8b230bbea96f3d46a0/ghc >--------------------------------------------------------------- commit e793a24ec0a05f64e1916a8b230bbea96f3d46a0 Author: Jared Weakly Date: Thu Jul 6 17:16:49 2017 -0700 Basic metrics collection and command line options working >--------------------------------------------------------------- e793a24ec0a05f64e1916a8b230bbea96f3d46a0 testsuite/driver/testlib.py | 1 + testsuite/driver/testutil.py | 11 ++++++----- 2 files changed, 7 insertions(+), 5 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index a5a97fa..3c18738 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1085,6 +1085,7 @@ def stats( name, way, stats_file ): # Check -t stats info def checkStats(name, way, stats_file, range_fields): + full_name = name + '(' + way + ')' result = passed() diff --git a/testsuite/driver/testutil.py b/testsuite/driver/testutil.py index 1fe1c20..a2386fe 100644 --- a/testsuite/driver/testutil.py +++ b/testsuite/driver/testutil.py @@ -3,7 +3,6 @@ import os import platform import subprocess import shutil - import threading def strip_quotes(s): @@ -50,14 +49,16 @@ def lndir(srcdir, dstdir): # This function allows one to read in git notes from the commandline # and then breaks it into a list of dictionaries that can be parsed # later on in the testing functions. -def parse_git_notes(namespace): - logFields = ['TEST_ENV','TEST','WAY','METRIC','VALUE'] - log = subprocess.check_output(['git', 'notes', '--ref=' + namespace, 'show']).decode('utf-8') +# I wanted to put it in perf_notes.py but couldn't figure out a nice way to do that. +def parse_git_notes(namespace, commit='HEAD'): + logFields = ['test_env','test','way','metric','value','commit'] + + log = subprocess.check_output(['git', 'notes', '--ref=' + namespace, 'show', commit]).decode('utf-8') log = log.strip('\n').split('\n') log = [line.strip('\t').split('\t') for line in log] + [x.append(commit) for x in log] log = [dict(zip(logFields, field)) for field in log] return log - # Add a print statement here if you want to see what's being loaded from git notes. # On Windows, os.symlink is not defined with Python 2.7, but is in Python 3 # when using msys2, as GHC does. Unfortunately, only Administrative users have From git at git.haskell.org Fri Jul 28 20:33:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 20:33:22 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: ONLY_PERF_TESTS=YES now fully implemented (a018862) Message-ID: <20170728203322.954593A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/a0188624b57d25f3741a7a41b319f8883600a86c/ghc >--------------------------------------------------------------- commit a0188624b57d25f3741a7a41b319f8883600a86c Author: Jared Weakly Date: Wed Jul 12 17:30:31 2017 -0700 ONLY_PERF_TESTS=YES now fully implemented >--------------------------------------------------------------- a0188624b57d25f3741a7a41b319f8883600a86c testsuite/driver/runtests.py | 2 ++ 1 file changed, 2 insertions(+) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index e0c652a..9af42bc 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -337,6 +337,8 @@ else: sys.stdout.flush() summary(t, sys.stdout, config.no_print_summary) + print("Only perf tests: " + str(config.only_perf_tests) + "\n") + print("Skip perf tests: " + str(config.skip_perf_tests) + "\n") # This here is loading up all of the git notes into memory. # It's most likely in the wrong spot and I haven't fully fleshed out From git at git.haskell.org Fri Jul 28 20:33:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 20:33:25 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Can now load up git note data into python (4fcf714) Message-ID: <20170728203325.55FFD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/4fcf7149b6e5015341f5f3daef3efda22b8d7c61/ghc >--------------------------------------------------------------- commit 4fcf7149b6e5015341f5f3daef3efda22b8d7c61 Author: Jared Weakly Date: Tue Jul 18 12:17:57 2017 -0700 Can now load up git note data into python >--------------------------------------------------------------- 4fcf7149b6e5015341f5f3daef3efda22b8d7c61 testsuite/driver/runtests.py | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index 9af42bc..bf7ee18 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -337,8 +337,10 @@ else: sys.stdout.flush() summary(t, sys.stdout, config.no_print_summary) - print("Only perf tests: " + str(config.only_perf_tests) + "\n") - print("Skip perf tests: " + str(config.skip_perf_tests) + "\n") + + if config.use_git_notes: + note = subprocess.check_output(["git","notes","--ref=perf","append","-m", "\n".join(config.accumulate_metrics)]) + parse_git_notes('perf') # Should this be hardcoded? Most likely not... # This here is loading up all of the git notes into memory. # It's most likely in the wrong spot and I haven't fully fleshed out From git at git.haskell.org Fri Jul 28 20:33:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 20:33:30 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Added initial metric comparison tooling (2826c2f) Message-ID: <20170728203330.CA5B03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/2826c2fe578c09f7a6f41d23358108cb13aeeba7/ghc >--------------------------------------------------------------- commit 2826c2fe578c09f7a6f41d23358108cb13aeeba7 Author: Jared Weakly Date: Thu Jul 20 17:30:21 2017 -0700 Added initial metric comparison tooling >--------------------------------------------------------------- 2826c2fe578c09f7a6f41d23358108cb13aeeba7 testsuite/driver/runtests.py | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index edeb226..0fce4be 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -338,14 +338,11 @@ else: summary(t, sys.stdout, config.no_print_summary) - # This here is loading up all of the git notes into memory. - # It's most likely in the wrong spot and I haven't fully fleshed out - # where exactly I'm putting this and how I'm refactoring the performance - # test running logic. - # Currently this is useful for debugging, at least. + # Write our accumulated metrics into the git notes for this commit. if config.use_git_notes: note = subprocess.check_output(["git","notes","--ref=perf","append","-m", "\n".join(config.accumulate_metrics)]) - parse_git_notes('perf') # Should this be hardcoded? Most likely not... + # v-- This is in a nonsensical area. It should be happening before all of the tests are even run. + # parse_git_notes('perf') # Should it even be happening in the test-driver logic anymore? # This here is loading up all of the git notes into memory. # It's most likely in the wrong spot and I haven't fully fleshed out From git at git.haskell.org Fri Jul 28 20:33:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 20:33:28 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Small changes to address Ben's comments (a16f043) Message-ID: <20170728203328.17BC63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/a16f043bd68a9f328f638fd4c7308715c99622b7/ghc >--------------------------------------------------------------- commit a16f043bd68a9f328f638fd4c7308715c99622b7 Author: Jared Weakly Date: Tue Jul 18 17:35:34 2017 -0700 Small changes to address Ben's comments Signed-off-by: Jared Weakly >--------------------------------------------------------------- a16f043bd68a9f328f638fd4c7308715c99622b7 testsuite/driver/runtests.py | 5 +++++ testsuite/driver/testlib.py | 1 - 2 files changed, 5 insertions(+), 1 deletion(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index bf7ee18..edeb226 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -338,6 +338,11 @@ else: summary(t, sys.stdout, config.no_print_summary) + # This here is loading up all of the git notes into memory. + # It's most likely in the wrong spot and I haven't fully fleshed out + # where exactly I'm putting this and how I'm refactoring the performance + # test running logic. + # Currently this is useful for debugging, at least. if config.use_git_notes: note = subprocess.check_output(["git","notes","--ref=perf","append","-m", "\n".join(config.accumulate_metrics)]) parse_git_notes('perf') # Should this be hardcoded? Most likely not... diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 3c18738..a5a97fa 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1085,7 +1085,6 @@ def stats( name, way, stats_file ): # Check -t stats info def checkStats(name, way, stats_file, range_fields): - full_name = name + '(' + way + ')' result = passed() From git at git.haskell.org Fri Jul 28 20:33:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 20:33:33 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: This should actually split things out this time (0636340) Message-ID: <20170728203333.85BEC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/0636340b20a7a958c0c1401059b30a1f17bdc5cd/ghc >--------------------------------------------------------------- commit 0636340b20a7a958c0c1401059b30a1f17bdc5cd Author: Jared Weakly Date: Wed Jul 26 13:52:07 2017 -0700 This should actually split things out this time >--------------------------------------------------------------- 0636340b20a7a958c0c1401059b30a1f17bdc5cd testsuite/driver/runtests.py | 24 ------------------------ 1 file changed, 24 deletions(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index f2f28d3..0fce4be 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -6,7 +6,6 @@ from __future__ import print_function -import argparse import signal import sys import os @@ -42,24 +41,6 @@ def signal_handler(signal, frame): # ----------------------------------------------------------------------------- # cmd-line options -# argparse implementation -# parser = argparse.ArgumentParser() -# parser.add_argument("configfile=", help="config file") -# parser.add_argument("config=", help="config field") -# parser.add_argument("rootdir=", help="root of tree containing tests (default: .)") -# parser.add_argument("summary-file=", help="file in which to save the (human-readable) summary") -# parser.add_argument("no-print-summary=", help="should we print the summary?") -# parser.add_argument("only=", help="just this test (can be give multiple --only= flags)") -# parser.add_argument("way=", help="just this way") -# parser.add_argument("skipway=", help="skip this way") -# parser.add_argument("threads=", help="threads to run simultaneously") -# parser.add_argument("check-files-written", help="check files aren't written by multiple tests") -# parser.add_argument("verbose=", help="verbose (0,1,2 so far)") -# parser.add_argument("skip-perf-tests", help="skip performance tests") -# parser.add_argument("only-perf-tests", help="Only do performance tests") -# parser.add_argument("use-git-notes", help="use git notes to store metrics. NOTE: This is expected to become the default and will eventually be taken out.") -# parser.add_argument("test-env=", help="Override default chosen test-env.") - long_options = [ "configfile=", # config file "config=", # config field @@ -79,11 +60,6 @@ long_options = [ ] opts, args = getopt.getopt(sys.argv[1:], "e:", long_options) -# argparse implementation -# aargs = parser.parse_args() - -# if aargs.configfile: -# exec(open(aarg.configfile)) for opt,arg in opts: if opt == '--configfile': From git at git.haskell.org Fri Jul 28 20:33:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 20:33:36 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Changed perf_notes quite a bit. Should be much closer to actually usable now (0bb481b) Message-ID: <20170728203336.EF0C23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/0bb481b45abb149661d2806d3fd11dde12997e52/ghc >--------------------------------------------------------------- commit 0bb481b45abb149661d2806d3fd11dde12997e52 Author: Jared Weakly Date: Sat Jul 22 20:18:22 2017 -0700 Changed perf_notes quite a bit. Should be much closer to actually usable now >--------------------------------------------------------------- 0bb481b45abb149661d2806d3fd11dde12997e52 testsuite/driver/perf_notes.py | 84 +++++++++++++++++++++++++++++++++++++++--- testsuite/driver/runtests.py | 24 ++++++++++++ testsuite/driver/test_val | 76 ++++++++++++++++++++++++++++++++++++++ 3 files changed, 179 insertions(+), 5 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 0bb481b45abb149661d2806d3fd11dde12997e52 From git at git.haskell.org Fri Jul 28 20:33:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 20:33:42 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Cleaning up my trash code for the perf_notes comparison tool (316fb9a) Message-ID: <20170728203342.700123A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/316fb9ad6b411c02181225285e9338110ae491a9/ghc >--------------------------------------------------------------- commit 316fb9ad6b411c02181225285e9338110ae491a9 Author: Jared Weakly Date: Sat Jul 22 20:48:48 2017 -0700 Cleaning up my trash code for the perf_notes comparison tool >--------------------------------------------------------------- 316fb9ad6b411c02181225285e9338110ae491a9 testsuite/driver/perf_notes.py | 105 +++++++++++++---------------------------- 1 file changed, 34 insertions(+), 71 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 316fb9ad6b411c02181225285e9338110ae491a9 From git at git.haskell.org Fri Jul 28 20:33:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 20:33:52 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Merge remote-tracking branch 'origin/master' into wip/perf-testsuite (7d0754a) Message-ID: <20170728203352.246883A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/7d0754a95b01abc7ed36624821e367648d873ad6/ghc >--------------------------------------------------------------- commit 7d0754a95b01abc7ed36624821e367648d873ad6 Merge: cf2669b d08b9cc Author: Jared Weakly Date: Fri Jul 28 13:28:29 2017 -0700 Merge remote-tracking branch 'origin/master' into wip/perf-testsuite >--------------------------------------------------------------- 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 7d0754a95b01abc7ed36624821e367648d873ad6 From git at git.haskell.org Fri Jul 28 20:33:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 20:33:48 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Prepare branch for merging in argparse from master (cf2669b) Message-ID: <20170728203348.3EC613A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/cf2669b52385476daf6a703cdaf1f025c59ef7dc/ghc >--------------------------------------------------------------- commit cf2669b52385476daf6a703cdaf1f025c59ef7dc Merge: bf5ee28 6dee76d Author: Jared Weakly Date: Fri Jul 28 11:44:30 2017 -0700 Prepare branch for merging in argparse from master >--------------------------------------------------------------- cf2669b52385476daf6a703cdaf1f025c59ef7dc utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Jul 28 20:33:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 20:33:39 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Greatly improved printing. Fixed the delta function. Made things simpler (bf5ee28) Message-ID: <20170728203339.A935A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/bf5ee28b0660e85e972472a48393f12ae6e7884e/ghc >--------------------------------------------------------------- commit bf5ee28b0660e85e972472a48393f12ae6e7884e Author: Jared Weakly Date: Wed Jul 26 18:30:37 2017 -0700 Greatly improved printing. Fixed the delta function. Made things simpler Signed-off-by: Jared Weakly >--------------------------------------------------------------- bf5ee28b0660e85e972472a48393f12ae6e7884e testsuite/driver/perf_notes.py | 104 +++++++++++++++++++---------------------- 1 file changed, 47 insertions(+), 57 deletions(-) diff --git a/testsuite/driver/perf_notes.py b/testsuite/driver/perf_notes.py index 2e9273d..ffa7656 100644 --- a/testsuite/driver/perf_notes.py +++ b/testsuite/driver/perf_notes.py @@ -8,8 +8,6 @@ # metrics between measurements taken for given commits in the environment given # by --test-env. -from __future__ import print_function - # TODO: Actually figure out what imports I need. import argparse import re @@ -26,11 +24,12 @@ parser.add_argument("--test-name", help="Optional: If given, filters table to include only \ tests matching the given regular expression.") # This is always going to be the last processing done on the metrics list because of how destructive it is. -parser.add_argument("--min-delta", +parser.add_argument("--min-delta",type=float, help="Optional: Display only tests where the relative \ spread is greater than the given value.") -parser.add_argument("--add-note", nargs=2, - help="Development only. Adds N fake metrics to the given commit") +parser.add_argument("--add-note", nargs=3, + help="Development only. Adds N fake metrics to the given commit. \ + The third argument is a useless flag to add some functionality.") parser.add_argument("commits", nargs=argparse.REMAINDER, help="The rest of the arguments will be the commits that will be used.") @@ -40,83 +39,74 @@ args = parser.parse_args() env = 'local' name = re.compile('.*') # metrics is a dictionary of the form -# {commit_1 : parse_git_notes, commit_2 : parse_git_notes, ... } -metrics = {} +# [ {'test_env': 'local', 'test': 'T100', 'way': 'some_way', 'metric': 'some_field', 'value': '1000', 'commit': 'HEAD'} ] +metrics = [] if args.commits: - metrics = dict(zip(args.commits, [parse_git_notes('perf',[c]) for c in args.commits])) + for c in args.commits: + metrics += parse_git_notes('perf',c) if args.test_env: - temp = [] - for commit in metrics: - temp.append([test for test in metrics.get(commit) if test['TEST_ENV'] == args.test_env]) - - metrics = dict(zip(metrics.keys(),temp)) + metrics = [test for test in metrics if test['test_env'] == args.test_env] if args.test_name: name = re.compile(args.test_name) - temp = [] - for commit in metrics: - temp.append([test for test in metrics.get(commit) if name.search(test.get('TEST',''))]) - - metrics = dict(zip(metrics.keys(),temp)) + metrics = [test for test in metrics if name.search(test.get('test',''))] if args.min_delta: - delta = 1.0 - float(args.min_delta) + delta = args.min_delta + print(delta) + # Took me way too long to realize I had the math utterly borked for the comparison def cmp(v1, v2): - return (v1/v2) > delta + if v1 > v2: + return (100 * (v1 - v2)/v2) > delta + else: + return (100 * (v2 - v1)/v1) > delta # I only want to compare the first commit with everything else. # So go through every item in the first commit and look up that test in # the other commits. Keep the falses. - m = [] # tempy variable because I don't know how to do this better without internet. - for tst in metrics.get(list(metrics.keys())[0]): - for k in list(metrics.keys())[1:]: # Because I needed a separate iterator for this somehow - for t in metrics.get(k): - if (t['TEST'] == tst['TEST']): - m.append((tst,t)) # Pairing off matching test names across commits. + latest_commit = [t for t in metrics if t['commit'] == args.commits[0]] + + m = [] # tempy variable + for t in latest_commit: + m += [(t,test) for test in metrics if (t['test'] == test['test']) and (t['commit'] != test['commit'])] deltas = [] - for k,v in m: + for fst,snd in m: # So... Much... Casting... oh my gawd. - if (not cmp(float(k['VALUE']),float(v['VALUE']))): - deltas.append(k) + if cmp(float(fst['value']),float(snd['value'])): + deltas.append(fst) - # metrics :: { commit : [ {tests} ] } - metrics = { list(metrics.keys())[0] : deltas } + metrics = deltas if args.add_note: - def note_gen(n, commit): + def note_gen(n, commit, delta=''): note = [] # To generate good testing data, I need some similar test names, test metrics, environments in every commit. # I also need some same tests but different metric values, same test name, different test environment names, etc. # This will do for now, but it's not really sufficient. # There's a better test_metrics = {} dictionary I just stuck in a file for now. - [note.append('\t'.join(['local', 'T'+ str(i*100), 'some_way', 'some_field', str(i*1000)])) for i in range(1,int(n)+1)] + if not delta: + [note.append('\t'.join(['local', 'T'+ str(i*100), 'some_way', 'some_field', str(i*1000)])) for i in range(1,int(int(n)/2)+1)] + [note.append('\t'.join(['non-local', 'W'+ str(i*100), 'other_way', 'other_field', str(i*100)])) for i in range(int(int(n)/2)+1,int(n)+1)] + if delta: + [note.append('\t'.join(['local', 'T'+ str(i*100), 'some_way', 'some_field', str(i*10)])) for i in range(1,int(int(n)/2)+1)] + [note.append('\t'.join(['non-local', 'W'+ str(i*100), 'other_way', 'other_field', str(i*1)])) for i in range(int(int(n)/2)+1,int(n)+1)] + git_note = subprocess.check_output(["git","notes","--ref=perf","append",commit,"-m", "\n".join(note)]) - note_gen(args.add_note[0],args.add_note[1]) - - -# At this point, since metrics is a { commit : [lst of tests] } variable, -# it should be pretty workable hopefully. -print(metrics) - -# It'll be best to go through the newest commit (the one we care about) -# and find all matching TESTS and then make a table of comparisons. -# If there's a test in the newest commit that doesn't exist in older ones, -# - should I just ignore it? -# - should I just print it as a one line table? -# - -# TEST: tst | METRIC: mtrk -# ----------+------------ -# commit1 | value -# commit2 | value -# ... | ... -# commitN | value - -print("{:<12} {:<10} {:<10} {:<20} {:<15}".format('TEST_ENV','TEST','WAY','METRIC','VALUE')) -for key in metrics: - print("{:<12} {:<10} {:<10} {:<20} {:<15}" - .format(key['TEST_ENV'],key['TEST'],key['WAY'],key['METRIC'],key['VALUE'])) + note_gen(args.add_note[0],args.add_note[1],args.add_note[2]) + +latest_commit = [t for t in metrics if t['commit'] == args.commits[0]] +rest = [t for t in metrics if t['commit'] != args.commits[0]] + +for test in latest_commit: + print("{:<13} {:5} {:<13}".format('TEST: ' + test['test'], ' | ', 'METRIC: ' + test['metric'])) + print("-------------------------------") + print("{:<13} {:5} {:<13}".format('commit:' + test['commit'], ' | ', test['value'])) + for t in rest: + if t['test'] == test['test']: + print("{:<13} {:5} {:<13}".format('commit:' + t['commit'], ' | ', t['value'])) + print('\n') From git at git.haskell.org Fri Jul 28 20:33:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 20:33:45 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite: Initial tooling to compare across commits (but for actual this time) (fcd90f8) Message-ID: <20170728203345.732593A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/perf-testsuite Link : http://ghc.haskell.org/trac/ghc/changeset/fcd90f8e590879d8f53448e7757a7901250b21f8/ghc >--------------------------------------------------------------- commit fcd90f8e590879d8f53448e7757a7901250b21f8 Author: Jared Weakly Date: Thu Jul 20 17:43:27 2017 -0700 Initial tooling to compare across commits (but for actual this time) >--------------------------------------------------------------- fcd90f8e590879d8f53448e7757a7901250b21f8 testsuite/driver/perf_notes.py | 85 ++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 85 insertions(+) diff --git a/testsuite/driver/perf_notes.py b/testsuite/driver/perf_notes.py new file mode 100644 index 0000000..ea289fc --- /dev/null +++ b/testsuite/driver/perf_notes.py @@ -0,0 +1,85 @@ +#1/usr/bin/env python3 + +# +# (c) Jared Weakly 2017 +# +# This file will be a utility to help facilitate the comparison of performance +# metrics across arbitrary commits. The file will produce a table comparing +# metrics between measurements taken for given commits in the environment given +# by --test-env. +# +# The file will also (for now) exist as a library to import git-note +# functionality for the project into other files so everywhere has access to +# functions such as parse_git_notes. +# +# It will take a few arguments: +# --test-env= +# --test-name= (optional: If given, filters table to include only tests matching the given regular expression.) +# --min-delta= (optional: Display only tests where the relative spread is greater than the given value.) +# All following arguments will be the commits to compare. + +from __future__ import print_function + +# TODO: Actually figure out what imports I need. +import argparse +import re +import os +import string +import subprocess + +from testutil import parse_git_notes + +# --------- Comparison Utilities -------- # +parser = argparse.ArgumentParser() +parser.add_argument("--test-env", + help="The given test environment to be compared.") #, + # required=True) # Should I make this required? +parser.add_argument("--test-name", + help="Optional: If given, filters table to include only \ + tests matching the given regular expression.") +parser.add_argument("--min-delta", + help="Optional: Display only tests where the relative \ + spread is greater than the given value.") +parser.add_argument("commits", nargs=argparse.REMAINDER) + +args = parser.parse_args() + +# Defaults +env = 'local' +name = re.compile('.*') +metrics = [] + +# I should figure out a nice way to mark data with the commit it comes from +# so that I can display test performance numbers in order from oldest to newest commit. +if args.commits: + print(args.commits) + metrics = parse_git_notes('perf',args.commits) + +if args.test_env: + env = args.test_env + metrics = [test for test in metrics if test['TEST_ENV'] == env] + +if args.test_name: + name = re.compile(args.test_name) + metrics = [test for test in metrics if name.search(test.get('TEST',''))] + +# Logic should probably go here to sort, group, and otherwise prepare the list +# of dicts for being pretty printed. +print(metrics) + +# I'll redo this table almost entirely, it's just a proof of concept for now. +# Ideally the list of metrics should be grouped by same test and organized from oldest to newest commits +# and each test will have its own small paragraph. I'm envisioning something like: +# -------------------------------- +# Test Foo: test_env, test_way, metric +# --------------------------------- +# commit1 commit2 commit3 ... +# number1 number2 number3 ... +# +# Gosh, I want to just print a list of dictionaries pretty like but don't want to just add some random dependency... +# Table is hardcoded and pretty ugly, but... it works. +# For now, this table just pretty prints the list of dictionaries. +print("{:<12} {:<10} {:<10} {:<20} {:<15}".format('TEST_ENV','TEST','WAY','METRIC','VALUE')) +for key in metrics: + print("{:<12} {:<10} {:<10} {:<20} {:<15}" + .format(key['TEST_ENV'],key['TEST'],key['WAY'],key['METRIC'],key['VALUE'])) From git at git.haskell.org Fri Jul 28 20:33:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 20:33:54 +0000 (UTC) Subject: [commit: ghc] wip/perf-testsuite's head updated: Merge remote-tracking branch 'origin/master' into wip/perf-testsuite (7d0754a) Message-ID: <20170728203354.CBEC03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/perf-testsuite' now includes: fefcbfa build system: Ensure there are no duplicate files in bindist list acbbb50 Fix ungrammatical error message cbbf083 fix dllwrap issue. c1d9690 Avoid linear lookup in unload_wkr in the Linker ee1047e Update autoconf scripts 98ab12a distrib/configure: Carry FFI include/lib paths from source distribution fb08252 users-guide: Improve legibility of OverlappingInstances documentation 0ae0f46 Preserve HaskellHaveRTSLinker in bindist 646ec0e Bump a bunch of submodules b8afdaf Update release notes for 8.2.1 fb17cc5 Bump integer-gmp version ecc9e9a ghc-prim: Bump version d4e9721 testsuite: Fix cabal01 for real this time 44b090b users-guide: Standardize and repair all flag references c945195 users-guide: Fix various wibbles 2dff2c7 Fix more documentation wibbles 145f1c7 Remove 8.0.2 release notes file 88f20bd Add a caveat to the GHC.Generics examples about :+: nesting a602b65 users-guides: Fix errant whitespace 0c04d78 users-guide: Cross-reference more flags 58b62d6 users-guide: Eliminate some redundant index entries 3e5d0f1 users-guide: Make it easier to reference haddocks 897366a users-guide: Fix URL of deferred type errors paper 85a295d ghc-prim: Don't allocate a thunk for each unpacked UTF-8 character 8a8cee7 DynFlags: Drop rtsBuildTag field d8051c6 Use libpthread instead of libthr on FreeBSD 8ec7770 testsuite: Add testcase for #13168 2183ac1 Fix import error with -XPackageImports when the module has a duplicate name 58545fd base: Introduce GHC.ByteOrder 104c72b Expose FrontendPluginAction 7d1909a Remove unused language pragma 36b270a Revert "Remove unused language pragma" 6bb32ba Fix #10684 by processing deriving clauses with finer grain 746ab0b Add an Outputable instance for ListMap 75bf11c Fix binder visiblity for default methods 6386fc3 Comments and tc-tracing only f959624 Comments only d31181b Test Trac #14033 362339d Fix note references and some typos d774b4e Fix #13968 by consulting isBuiltInOcc_maybe 4a26415 Remove unneeded import 8e15e3d Improve error messages around kind mismatches. c9667d3 Fix #11400, #11560 by documenting an infelicity. 9a54975 Test #11672 in typecheck/should_fail/T11672. ef39af7 Don't tidy vars when dumping a type bb2a446 Preserve CoVar uniques during pretty printing 79cfb19 Remove old coercion pretty-printer c2417b8 Fix #13819 by refactoring TypeEqOrigin.uo_thing fb75213 Track visibility in TypeEqOrigin 10d13b6 Fix #11963 by checking for more mixed type/kinds ca47186 Document that type holes kill polymorphic recursion 1696dbf Fix #12176 by being a bit more careful instantiating. 4239238 Fix #12369 by being more flexible with data insts 791947d Refactor tcInferApps. 7af0b90 Initialize hs_init with UTF8 encoded arguments on Windows. 6b77914 Fix instantiation of pattern synonyms af6d225 Remove redundant constraint in context b1317a3 Fix ASSERT failure in tc269 452755d Do not discard insolubles in implications ad0037e Add DebugCallStack to piResultTy d618649 Error eagerly after renaming failures in reifyInstances b3b564f Merge types and kinds in DsMeta 424ecad Add regression tests for #13601, #13780, #13877 5e940bd Switched out optparse for argparse in runtests.py 54d3a1f testsuite: Produce JUnit output 262bb95 testsuite: Add test for #14028 274e9b2 Add “BINARY_DIST_DIR” to Makefile dac4b9d ByteCodeGen: use byte indexing for BCenv 2974f81 Fix lld detection if both gold and lld are found f134bfb gitmodules: Delete entry for dead hoopl submodule d08b9cc configure: Ensure that user's LD setting is respected 83a482c Basic metrics collection and command line options working b4a9820 ONLY_PERF_TESTS=YES now fully implemented df78afc Can now load up git note data into python e04118d Small changes to address Ben's comments e793a24 Basic metrics collection and command line options working a018862 ONLY_PERF_TESTS=YES now fully implemented 4fcf714 Can now load up git note data into python a16f043 Small changes to address Ben's comments 2826c2f Added initial metric comparison tooling fcd90f8 Initial tooling to compare across commits (but for actual this time) 0bb481b Changed perf_notes quite a bit. Should be much closer to actually usable now 316fb9a Cleaning up my trash code for the perf_notes comparison tool 0636340 This should actually split things out this time bf5ee28 Greatly improved printing. Fixed the delta function. Made things simpler cf2669b Prepare branch for merging in argparse from master 7d0754a Merge remote-tracking branch 'origin/master' into wip/perf-testsuite From git at git.haskell.org Fri Jul 28 23:07:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 23:07:15 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Testing simpler Jenkinsfile (4e673bd) Message-ID: <20170728230715.5DF0E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/4e673bd5db9163e0213099e05f8bed2076531169/ghc >--------------------------------------------------------------- commit 4e673bd5db9163e0213099e05f8bed2076531169 Author: Ben Gamari Date: Fri Apr 21 14:29:34 2017 -0400 Testing simpler Jenkinsfile >--------------------------------------------------------------- 4e673bd5db9163e0213099e05f8bed2076531169 Jenkinsfile | 366 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Makefile | 4 + ghc.mk | 4 + mk/config.mk.in | 2 +- 4 files changed, 375 insertions(+), 1 deletion(-) 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 4e673bd5db9163e0213099e05f8bed2076531169 From git at git.haskell.org Fri Jul 28 23:07:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 23:07:20 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix JUnit (a4b94e3) Message-ID: <20170728230720.F1E893A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a4b94e3a4164ce20c3436504f73f34a66f72ba7b/ghc >--------------------------------------------------------------- commit a4b94e3a4164ce20c3436504f73f34a66f72ba7b Author: Ben Gamari Date: Fri Jul 28 19:06:29 2017 -0400 Fix JUnit >--------------------------------------------------------------- a4b94e3a4164ce20c3436504f73f34a66f72ba7b Jenkinsfile | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index ee6a884..23b6ced 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -302,8 +302,8 @@ def testGhc(params) { if (params.nightly) { target = 'slowtest' } - sh "${makeCmd} -Ctestsuite/tests LOCAL=0 BINDIST=YES THREADS=${env.THREADS} TEST_HC=\"${testGhc}\" ${target}" - junit 'testsuite*.xml' + sh "${makeCmd} -Ctestsuite/tests LOCAL=0 BINDIST=YES THREADS=${env.THREADS} TEST_HC=\"${testGhc}\" JUNIT_FILE=testsuite.xml ${target}" + junit 'testsuite.xml' } } } From git at git.haskell.org Fri Jul 28 23:07:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Jul 2017 23:07:18 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Delete hoopl submodule gitmodules entry (fed8fe5) Message-ID: <20170728230718.1E4943A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/fed8fe5ea94166a47fcb421612ecc97a91db7dc4/ghc >--------------------------------------------------------------- commit fed8fe5ea94166a47fcb421612ecc97a91db7dc4 Author: Ben Gamari Date: Fri Jul 28 13:31:32 2017 -0400 Delete hoopl submodule gitmodules entry >--------------------------------------------------------------- fed8fe5ea94166a47fcb421612ecc97a91db7dc4 .gitmodules | 4 ---- 1 file changed, 4 deletions(-) diff --git a/.gitmodules b/.gitmodules index 55d360a..07ed3b7 100644 --- a/.gitmodules +++ b/.gitmodules @@ -70,10 +70,6 @@ path = libraries/filepath url = ../packages/filepath.git ignore = none -[submodule "libraries/hoopl"] - path = libraries/hoopl - url = ../packages/hoopl.git - ignore = none [submodule "libraries/hpc"] path = libraries/hpc url = ../packages/hpc.git From git at git.haskell.org Sat Jul 29 14:34:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Jul 2017 14:34:30 +0000 (UTC) Subject: [commit: ghc] master: Ensure that we always link against libm (0e3c101) Message-ID: <20170729143430.199523A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0e3c10160472df082fd3decd98c2489a2f8e68bd/ghc >--------------------------------------------------------------- commit 0e3c10160472df082fd3decd98c2489a2f8e68bd Author: Ben Gamari Date: Fri Jul 28 13:41:04 2017 -0400 Ensure that we always link against libm ld.gold is particularly picky that we declare all of our link dependencies on Nix. See #14022. Test Plan: Validate on Nix Reviewers: austin Subscribers: hvr, rwbarton, thomie GHC Trac Issues: #14022 Differential Revision: https://phabricator.haskell.org/D3787 >--------------------------------------------------------------- 0e3c10160472df082fd3decd98c2489a2f8e68bd compiler/main/DriverPipeline.hs | 1 + compiler/main/SysTools.hs | 14 ++++++++++++++ 2 files changed, 15 insertions(+) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 3fc35e5..7f70377 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1932,6 +1932,7 @@ linkBinary' staticLink dflags o_files dep_packages = do ++ [ SysTools.Option "-o" , SysTools.FileOption "" output_fn ] + ++ libmLinkOpts ++ map SysTools.Option ( [] diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs index 3d16124..c73e47c 100644 --- a/compiler/main/SysTools.hs +++ b/compiler/main/SysTools.hs @@ -39,6 +39,9 @@ module SysTools ( Option(..), + -- platform-specifics + libmLinkOpts, + -- frameworks getPkgFrameworkOpts, getFrameworkOpts @@ -1537,6 +1540,7 @@ linkDynLib dflags0 o_files dep_packages runLink dflags ( map Option verbFlags + ++ libmLinkOpts ++ [ Option "-o" , FileOption "" output_fn ] @@ -1556,6 +1560,16 @@ linkDynLib dflags0 o_files dep_packages ++ map Option pkg_link_opts ) +-- | Some platforms require that we explicitly link against @libm@ if any +-- math-y things are used (which we assume to include all programs). See #14022. +libmLinkOpts :: [Option] +libmLinkOpts = +#if defined(HAVE_LIBM) + [Option "-lm"] +#else + [] +#endif + getPkgFrameworkOpts :: DynFlags -> Platform -> [InstalledUnitId] -> IO [String] getPkgFrameworkOpts dflags platform dep_packages | platformUsesFrameworks platform = do From git at git.haskell.org Sat Jul 29 14:34:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Jul 2017 14:34:32 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Don't pass allow_abbrev (0e3eacc) Message-ID: <20170729143432.D02B53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0e3eacc7191593ca61992b044a3875dbb50903e6/ghc >--------------------------------------------------------------- commit 0e3eacc7191593ca61992b044a3875dbb50903e6 Author: Ben Gamari Date: Fri Jul 28 18:23:55 2017 -0400 testsuite: Don't pass allow_abbrev This is only supported by Python 3.5 and later, which is too new for us to rely on. Reviewers: austin Subscribers: rwbarton, thomie, RyanGlScott GHC Trac Issues: #14050 Differential Revision: https://phabricator.haskell.org/D3803 >--------------------------------------------------------------- 0e3eacc7191593ca61992b044a3875dbb50903e6 testsuite/driver/runtests.py | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index f0c635f..3e03ed3 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -42,8 +42,7 @@ def signal_handler(signal, frame): # ----------------------------------------------------------------------------- # cmd-line options -parser = argparse.ArgumentParser(description="GHC's testsuite driver", - allow_abbrev=False) +parser = argparse.ArgumentParser(description="GHC's testsuite driver") parser.add_argument("-e", action='append', help="A string to execute from the command line.") parser.add_argument("--config-file", action="append", help="config file") From git at git.haskell.org Sat Jul 29 14:34:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Jul 2017 14:34:35 +0000 (UTC) Subject: [commit: ghc] master: Remove unnecessary GHC option from SrcLoc (121fee9) Message-ID: <20170729143435.8BADB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/121fee99496d5f5d53a8cd6b08c13a0b6bb9069d/ghc >--------------------------------------------------------------- commit 121fee99496d5f5d53a8cd6b08c13a0b6bb9069d Author: Sven Tennie Date: Fri Jul 28 18:24:34 2017 -0400 Remove unnecessary GHC option from SrcLoc This was an old workaround for #5252. Fixes #13173. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3763 >--------------------------------------------------------------- 121fee99496d5f5d53a8cd6b08c13a0b6bb9069d compiler/basicTypes/SrcLoc.hs | 4 ---- 1 file changed, 4 deletions(-) diff --git a/compiler/basicTypes/SrcLoc.hs b/compiler/basicTypes/SrcLoc.hs index f71dac6..1e6e7d2 100644 --- a/compiler/basicTypes/SrcLoc.hs +++ b/compiler/basicTypes/SrcLoc.hs @@ -7,10 +7,6 @@ {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE RecordWildCards #-} -{-# OPTIONS_GHC -fno-omit-interface-pragmas #-} - -- Workaround for Trac #5252 crashes the bootstrap compiler without -O - -- When the earliest compiler we want to boostrap with is - -- GHC 7.2, we can make RealSrcLoc properly abstract -- | This module contains types that relate to the positions of things -- in source files, and allow tagging of those things with locations From git at git.haskell.org Sat Jul 29 14:34:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Jul 2017 14:34:39 +0000 (UTC) Subject: [commit: ghc] master: Fix hs-boot knot-tying with record wild cards. (9e9fb57) Message-ID: <20170729143439.011073A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9e9fb57c37c62bb6c90f15b173c5d3632121c66a/ghc >--------------------------------------------------------------- commit 9e9fb57c37c62bb6c90f15b173c5d3632121c66a Author: Edward Z. Yang Date: Fri Jul 28 18:25:12 2017 -0400 Fix hs-boot knot-tying with record wild cards. Fixes #13710. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: bgamari, austin, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #13710 Differential Revision: https://phabricator.haskell.org/D3743 >--------------------------------------------------------------- 9e9fb57c37c62bb6c90f15b173c5d3632121c66a compiler/iface/TcIface.hs | 9 ++++++++- testsuite/tests/driver/T13710/A.hs | 5 +++++ testsuite/tests/driver/T13710/A.hs-boot | 2 ++ testsuite/tests/{programs/hs-boot => driver/T13710}/B.hs | 4 +--- testsuite/tests/{cabal/pkg02 => driver/T13710}/Makefile | 2 ++ testsuite/tests/driver/T13710/T13710.stdout | 3 +++ testsuite/tests/driver/T13710/all.T | 4 ++++ 7 files changed, 25 insertions(+), 4 deletions(-) diff --git a/compiler/iface/TcIface.hs b/compiler/iface/TcIface.hs index b3119b2..9e06165 100644 --- a/compiler/iface/TcIface.hs +++ b/compiler/iface/TcIface.hs @@ -915,7 +915,14 @@ tcIfaceDataCons tycon_name tycon tc_tybinders if_cons ; ~(eq_spec, theta, arg_tys, stricts) <- forkM (mk_doc dc_name) $ do { eq_spec <- tcIfaceEqSpec spec ; theta <- tcIfaceCtxt ctxt - ; arg_tys <- mapM tcIfaceType args + -- This fixes #13710. The enclosing lazy thunk gets + -- forced when typechecking record wildcard pattern + -- matching (it's not completely clear why this + -- tuple is needed), which causes trouble if one of + -- the argument types was recursively defined. + -- See also Note [Tying the knot] + ; arg_tys <- forkM (mk_doc dc_name <+> text "arg_tys") + $ mapM tcIfaceType args ; stricts <- mapM tc_strict if_stricts -- The IfBang field can mention -- the type itself; hence inside forkM diff --git a/testsuite/tests/driver/T13710/A.hs b/testsuite/tests/driver/T13710/A.hs new file mode 100644 index 0000000..5181945 --- /dev/null +++ b/testsuite/tests/driver/T13710/A.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE RecordWildCards #-} +module A where +import B +data E = MkE +p (H{..}) = () diff --git a/testsuite/tests/driver/T13710/A.hs-boot b/testsuite/tests/driver/T13710/A.hs-boot new file mode 100644 index 0000000..94a2f5e --- /dev/null +++ b/testsuite/tests/driver/T13710/A.hs-boot @@ -0,0 +1,2 @@ +module A ( E ) where +data E diff --git a/testsuite/tests/programs/hs-boot/B.hs b/testsuite/tests/driver/T13710/B.hs similarity index 63% copy from testsuite/tests/programs/hs-boot/B.hs copy to testsuite/tests/driver/T13710/B.hs index 13d1ac4..87c93a9 100644 --- a/testsuite/tests/programs/hs-boot/B.hs +++ b/testsuite/tests/driver/T13710/B.hs @@ -1,5 +1,3 @@ - module B where - -import C import {-# SOURCE #-} A +data H = H { h :: E } diff --git a/testsuite/tests/cabal/pkg02/Makefile b/testsuite/tests/driver/T13710/Makefile similarity index 59% copy from testsuite/tests/cabal/pkg02/Makefile copy to testsuite/tests/driver/T13710/Makefile index 4a26853..d582f94 100644 --- a/testsuite/tests/cabal/pkg02/Makefile +++ b/testsuite/tests/driver/T13710/Makefile @@ -2,3 +2,5 @@ TOP=../../.. include $(TOP)/mk/boilerplate.mk include $(TOP)/mk/test.mk +T13710: + '$(TEST_HC)' $(TEST_HC_OPTS) --make B.hs diff --git a/testsuite/tests/driver/T13710/T13710.stdout b/testsuite/tests/driver/T13710/T13710.stdout new file mode 100644 index 0000000..2d72928 --- /dev/null +++ b/testsuite/tests/driver/T13710/T13710.stdout @@ -0,0 +1,3 @@ +[1 of 3] Compiling A[boot] ( A.hs-boot, A.o-boot ) +[2 of 3] Compiling B ( B.hs, B.o ) +[3 of 3] Compiling A ( A.hs, A.o ) diff --git a/testsuite/tests/driver/T13710/all.T b/testsuite/tests/driver/T13710/all.T new file mode 100644 index 0000000..64daacc --- /dev/null +++ b/testsuite/tests/driver/T13710/all.T @@ -0,0 +1,4 @@ +test('T13710', + [extra_files(['A.hs', 'A.hs-boot', 'B.hs'])], + run_command, + ['$MAKE -s --no-print-directory T13710']) From git at git.haskell.org Sat Jul 29 14:34:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Jul 2017 14:34:43 +0000 (UTC) Subject: [commit: ghc] master: Add rtsopts ignore and ignoreAll. (d75bba8) Message-ID: <20170729143443.134BB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d75bba852db208b1d9fcb84dab01598a765d2534/ghc >--------------------------------------------------------------- commit d75bba852db208b1d9fcb84dab01598a765d2534 Author: Andreas Klebinger Date: Fri Jul 28 18:25:24 2017 -0400 Add rtsopts ignore and ignoreAll. These ignore commandline arguments for ignore and commandline as well as GHCRTS arguments for ignoreAll. Passing RTS flags given on the command line along to the program by simply skipping processing of these flags by the RTS. This fixes #12870. Test Plan: ./validate Reviewers: austin, hvr, bgamari, erikd, simonmar Reviewed By: simonmar Subscribers: Phyx, rwbarton, thomie GHC Trac Issues: #12870 Differential Revision: https://phabricator.haskell.org/D3740 >--------------------------------------------------------------- d75bba852db208b1d9fcb84dab01598a765d2534 compiler/main/DynFlags.hs | 8 ++- docs/users_guide/phases.rst | 9 ++++ docs/users_guide/runtime_control.rst | 4 +- includes/RtsAPI.h | 2 + rts/RtsFlags.c | 62 +++++++++++++--------- testsuite/tests/rts/{T1791 => flags}/Makefile | 0 testsuite/tests/rts/flags/T12870.hs | 6 +++ .../{T1791/T1791.stdout => flags/T12870_.stdout} | 0 testsuite/tests/rts/flags/T12870a.stdout | 1 + testsuite/tests/rts/flags/T12870c.stderr | 1 + testsuite/tests/rts/flags/T12870d.stdout | 1 + testsuite/tests/rts/flags/T12870e.stdout | 1 + testsuite/tests/rts/flags/T12870f.stdout | 1 + testsuite/tests/rts/flags/T12870g.hs | 8 +++ testsuite/tests/rts/flags/T12870g.stdout | 1 + testsuite/tests/rts/flags/T12870h.stdout | 1 + testsuite/tests/rts/flags/all.T | 44 +++++++++++++++ 17 files changed, 122 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 d75bba852db208b1d9fcb84dab01598a765d2534 From git at git.haskell.org Sat Jul 29 14:34:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Jul 2017 14:34:45 +0000 (UTC) Subject: [commit: ghc] master: Ensure that GHC.Stack.callStack doesn't fail (84f8e86) Message-ID: <20170729143445.C396A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/84f8e86248d47f619a94c68260876a1258e0a931/ghc >--------------------------------------------------------------- commit 84f8e86248d47f619a94c68260876a1258e0a931 Author: Ben Gamari Date: Fri Jul 28 18:25:35 2017 -0400 Ensure that GHC.Stack.callStack doesn't fail Test Plan: Validate, ensure the `f7` program of `IPLocation` doesn't crash. Reviewers: gridaphobe, austin, hvr Reviewed By: gridaphobe Subscribers: rwbarton, thomie GHC Trac Issues: #14028 Differential Revision: https://phabricator.haskell.org/D3795 >--------------------------------------------------------------- 84f8e86248d47f619a94c68260876a1258e0a931 libraries/base/GHC/Stack.hs | 5 ++++- testsuite/tests/typecheck/should_run/IPLocation.hs | 6 ++++++ 2 files changed, 10 insertions(+), 1 deletion(-) diff --git a/libraries/base/GHC/Stack.hs b/libraries/base/GHC/Stack.hs index f5b175c..1f102c9 100644 --- a/libraries/base/GHC/Stack.hs +++ b/libraries/base/GHC/Stack.hs @@ -85,7 +85,10 @@ popCallStack stk = case stk of -- -- @since 4.9.0.0 callStack :: HasCallStack => CallStack -callStack = popCallStack ?callStack +callStack = + case ?callStack of + EmptyCallStack -> EmptyCallStack + _ -> popCallStack ?callStack {-# INLINE callStack #-} -- | Perform some computation without adding new entries to the 'CallStack'. diff --git a/testsuite/tests/typecheck/should_run/IPLocation.hs b/testsuite/tests/typecheck/should_run/IPLocation.hs index 75575e0..9647289 100644 --- a/testsuite/tests/typecheck/should_run/IPLocation.hs +++ b/testsuite/tests/typecheck/should_run/IPLocation.hs @@ -29,9 +29,15 @@ f6 0 = putStrLn $ prettyCallStack ?loc f6 n = f6 (n-1) -- recursive functions add a SrcLoc for each recursive call +f7 :: IO () +f7 = putStrLn (prettyCallStack $ id (\_ -> callStack) ()) + -- shouldn't crash. See #14043. + +main :: IO () main = do f0 f1 f3 (\ () -> putStrLn $ prettyCallStack ?loc) f4 (\ () -> putStrLn $ prettyCallStack ?loc) f5 (\ () -> putStrLn $ prettyCallStack ?loc3) f6 5 + f7 From git at git.haskell.org Sat Jul 29 14:34:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Jul 2017 14:34:49 +0000 (UTC) Subject: [commit: ghc] master: Add '<&>' operator to Data.Functor. '<&>' calls '<$>' with flipped arguments. (9cfabbb) Message-ID: <20170729143449.526BA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9cfabbb5267e72b8017d8dc04d8580f73f425aa8/ghc >--------------------------------------------------------------- commit 9cfabbb5267e72b8017d8dc04d8580f73f425aa8 Author: Sven Tennie Date: Fri Jul 28 18:25:50 2017 -0400 Add '<&>' operator to Data.Functor. '<&>' calls '<$>' with flipped arguments. This was proposed by David Feuer (https://mail.haskell.org/pipermail/libraries/2016-August/027293.html) and solves #14029. The implementation is a copy of the '<&>' operator in Control.Lens.Lens. Add tests for following Data.Functor operators: '<$>', '<&>', '<$' and '$>'. '<&>' was added for solving #14029. '<$>', '<$' and '$>' were probably untested. Reviewers: austin, hvr, bgamari, RyanGlScott Reviewed By: RyanGlScott Subscribers: RyanGlScott, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3800 >--------------------------------------------------------------- 9cfabbb5267e72b8017d8dc04d8580f73f425aa8 libraries/base/Data/Functor.hs | 26 +++++++++++++++++++ libraries/base/changelog.md | 2 ++ libraries/base/tests/all.T | 1 + libraries/base/tests/functorOperators.hs | 38 ++++++++++++++++++++++++++++ libraries/base/tests/functorOperators.stdout | 16 ++++++++++++ 5 files changed, 83 insertions(+) diff --git a/libraries/base/Data/Functor.hs b/libraries/base/Data/Functor.hs index 62bb709..2c0fbc3 100644 --- a/libraries/base/Data/Functor.hs +++ b/libraries/base/Data/Functor.hs @@ -20,6 +20,7 @@ module Data.Functor (<$), ($>), (<$>), + (<&>), void, ) where @@ -74,6 +75,31 @@ infixl 4 <$> infixl 4 $> +-- | Flipped version of '<$>'. +-- +-- @ +-- ('<&>') = 'flip' 'fmap' +-- @ +-- +-- @since 4.11.0.0 +-- +-- ==== __Examples__ +-- Apply @(+1)@ to a list, a 'Data.Maybe.Just' and a 'Data.Either.Right': +-- +-- >>> Just 2 <&> (+1) +-- Just 3 +-- +-- >>> [1,2,3] <&> (+1) +-- [2,3,4] +-- +-- >>> Right 3 <&> (+1) +-- Right 4 +-- +(<&>) :: Functor f => f a -> (a -> b) -> f b +as <&> f = f <$> as + +infixl 1 <&> + -- | Flipped version of '<$'. -- -- @since 4.7.0.0 diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 0cfd9c1..a9f2992 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -10,6 +10,8 @@ * Add `infixl 9 !!` declaration for `Data.List.NonEmpty.!!` + * Add `<&>` operator to `Data.Functor` (#14029) + ## 4.10.0.0 *April 2017* * Bundled with GHC *TBA* diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T index 4bd8084..b52a5d9 100644 --- a/libraries/base/tests/all.T +++ b/libraries/base/tests/all.T @@ -214,3 +214,4 @@ test('T13191', ['-O']) test('T13525', when(opsys('mingw32'), skip), compile_and_run, ['']) test('T13097', normal, compile_and_run, ['']) +test('functorOperators', normal, compile_and_run, ['']) diff --git a/libraries/base/tests/functorOperators.hs b/libraries/base/tests/functorOperators.hs new file mode 100644 index 0000000..aea5dfd --- /dev/null +++ b/libraries/base/tests/functorOperators.hs @@ -0,0 +1,38 @@ +-- Test infix operators of 'Functor' + +import Data.Functor + +main :: IO () +main = do + testInfixFmap + testFlippedInfixFmap + testInfixReplace + testFlippedInfixReplace + +testInfixFmap :: IO () +testInfixFmap = do + print "<$> tests:" + print $ (+ 1) <$> Just 2 -- => Just 3 + print (((+ 1) <$> Right 3) :: Either Int Int) -- => Right 4 + print $ (+ 1) <$> [1, 2, 3] -- => [2,3,4] + +testFlippedInfixFmap :: IO () +testFlippedInfixFmap = do + print "<&> tests:" + print $ Just 2 <&> (+ 1) -- => Just 3 + print ((Right 3 <&> (+ 1)) :: Either Int Int) -- => Right 4 + print $ [1, 2, 3] <&> (+ 1) -- => [2,3,4] + +testInfixReplace :: IO () +testInfixReplace = do + print "<$ tests:" + print $ 42 <$ Just 1 -- => Just 42 + print ((42 <$ Right 1) :: Either Int Int) -- => Right 42 + print $ 42 <$ [1, 2, 3] -- => [42,42,42] + +testFlippedInfixReplace :: IO () +testFlippedInfixReplace = do + print "$> tests:" + print $ Just 1 $> 42 -- => Just 42 + print ((Right 1 $> 42) :: Either Int Int) -- => Right 42 + print $ [1, 2, 3] $> 42 -- => [42,42,42] diff --git a/libraries/base/tests/functorOperators.stdout b/libraries/base/tests/functorOperators.stdout new file mode 100644 index 0000000..00a17ed --- /dev/null +++ b/libraries/base/tests/functorOperators.stdout @@ -0,0 +1,16 @@ +"<$> tests:" +Just 3 +Right 4 +[2,3,4] +"<&> tests:" +Just 3 +Right 4 +[2,3,4] +"<$ tests:" +Just 42 +Right 42 +[42,42,42] +"$> tests:" +Just 42 +Right 42 +[42,42,42] From git at git.haskell.org Sat Jul 29 15:32:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Jul 2017 15:32:20 +0000 (UTC) Subject: [commit: ghc] master: Fix #14045 by omitting an unnecessary check (d1ef223) Message-ID: <20170729153220.11D393A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d1ef223cfebd23c25489a4b0c67fbaa2f91c1ec6/ghc >--------------------------------------------------------------- commit d1ef223cfebd23c25489a4b0c67fbaa2f91c1ec6 Author: Richard Eisenberg Date: Fri Jul 28 21:43:38 2017 -0400 Fix #14045 by omitting an unnecessary check Previously, we checked the number of patterns in a data instances for all data families whose kind did not end in a kind variable. But, of course, undersaturating instances can happen even without the kind ending in a kind variable. So I've omitted the arity check. Data families aren't as particular about their arity as type families are (because data families can be undersaturated). Still, this change degrades error messages when instances don't have the right arity; now, instead of reporting a simple mismatch in the number of patterns, GHC reports kind errors. The new errors are fully accurate, but perhaps not as easy to work with. Still, with the new flexibility of allowing data family instances with varying numbers of patterns, I don't see a better way. This commit also improves source fidelity in some error messages, requiring more changes than really are necessary. But without these changes, error messages around mismatched associated instance heads were poor. test cases: indexed-types/should_compile/T14045, indexed-types/should_fail/T14045a >--------------------------------------------------------------- d1ef223cfebd23c25489a4b0c67fbaa2f91c1ec6 compiler/hsSyn/HsDecls.hs | 22 ++++--- compiler/typecheck/TcGenDeriv.hs | 3 +- compiler/typecheck/TcHsType.hs | 11 ++-- compiler/typecheck/TcInstDcls.hs | 12 ++-- compiler/typecheck/TcTyClsDecls.hs | 76 ++++++++++++---------- compiler/typecheck/TcValidity.hs | 20 +++--- .../tests/indexed-types/should_compile/T14045.hs | 10 +++ testsuite/tests/indexed-types/should_compile/all.T | 1 + .../indexed-types/should_fail/SimpleFail1a.stderr | 3 +- .../indexed-types/should_fail/SimpleFail1b.stderr | 2 +- .../indexed-types/should_fail/SimpleFail2a.stderr | 2 +- .../tests/indexed-types/should_fail/T14045a.hs | 13 ++++ .../tests/indexed-types/should_fail/T14045a.stderr | 7 ++ testsuite/tests/indexed-types/should_fail/all.T | 1 + 14 files changed, 116 insertions(+), 67 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 d1ef223cfebd23c25489a4b0c67fbaa2f91c1ec6 From git at git.haskell.org Sun Jul 30 00:04:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Jul 2017 00:04:13 +0000 (UTC) Subject: [commit: ghc] master: Add regression test for #14055 (f839b9d) Message-ID: <20170730000413.F327C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f839b9de18a9f795e438314bea9f17e594afa354/ghc >--------------------------------------------------------------- commit f839b9de18a9f795e438314bea9f17e594afa354 Author: Ryan Scott Date: Sat Jul 29 19:35:52 2017 -0400 Add regression test for #14055 >--------------------------------------------------------------- f839b9de18a9f795e438314bea9f17e594afa354 testsuite/tests/typecheck/should_fail/T14055.hs | 6 ++++++ testsuite/tests/typecheck/should_fail/T14055.stderr | 6 ++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 13 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T14055.hs b/testsuite/tests/typecheck/should_fail/T14055.hs new file mode 100644 index 0000000..996c33b --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T14055.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE DataKinds, TypeFamilies #-} + +newtype X = RollX (() -> X) + +type family F t :: X where + F t = RollX (t -> ()) diff --git a/testsuite/tests/typecheck/should_fail/T14055.stderr b/testsuite/tests/typecheck/should_fail/T14055.stderr new file mode 100644 index 0000000..19e4d59 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T14055.stderr @@ -0,0 +1,6 @@ + +T14055.hs:6:18: error: + • Expected kind ‘() -> X’, but ‘t -> ()’ has kind ‘*’ + • In the first argument of ‘RollX’, namely ‘(t -> ())’ + In the type ‘RollX (t -> ())’ + In the type family declaration for ‘F’ diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index e31c7ee..d865c76 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -453,3 +453,4 @@ test('T11672', normal, compile_fail, ['']) test('T13819', normal, compile_fail, ['']) test('T11963', normal, compile_fail, ['']) test('T14000', normal, compile_fail, ['']) +test('T14055', normal, compile_fail, ['']) From git at git.haskell.org Sun Jul 30 00:04:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Jul 2017 00:04:17 +0000 (UTC) Subject: [commit: ghc] master: Follow-up to #13887, for promoted infix constructors (7089dc2) Message-ID: <20170730000417.8757E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7089dc2f12f9616771fc1de143e9b974157405d8/ghc >--------------------------------------------------------------- commit 7089dc2f12f9616771fc1de143e9b974157405d8 Author: Ryan Scott Date: Sat Jul 29 19:36:42 2017 -0400 Follow-up to #13887, for promoted infix constructors Summary: Correct a couple more spots in the TH pretty-printer by applying the appropriate parenthesization for infix names. Fixes #13887 (again). Test Plan: make test TEST=T13887 Reviewers: austin, bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13887 Differential Revision: https://phabricator.haskell.org/D3802 >--------------------------------------------------------------- 7089dc2f12f9616771fc1de143e9b974157405d8 libraries/template-haskell/Language/Haskell/TH/Ppr.hs | 4 ++-- testsuite/tests/th/T13887.hs | 13 +++++++++++++ testsuite/tests/th/T13887.stdout | 3 +++ testsuite/tests/th/TH_PromotedList.stderr | 4 ++-- testsuite/tests/th/TH_RichKinds2.stderr | 5 +++-- testsuite/tests/th/all.T | 1 + 6 files changed, 24 insertions(+), 6 deletions(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs index 696c445..e6c3302 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs @@ -689,11 +689,11 @@ pprParendType (UnboxedSumT arity) = hashParens $ hcat $ replicate (arity-1) bar pprParendType ArrowT = parens (text "->") pprParendType ListT = text "[]" pprParendType (LitT l) = pprTyLit l -pprParendType (PromotedT c) = text "'" <> ppr c +pprParendType (PromotedT c) = text "'" <> pprName' Applied c pprParendType (PromotedTupleT 0) = text "'()" pprParendType (PromotedTupleT n) = quoteParens (hcat (replicate (n-1) comma)) pprParendType PromotedNilT = text "'[]" -pprParendType PromotedConsT = text "(':)" +pprParendType PromotedConsT = text "'(:)" pprParendType StarT = char '*' pprParendType ConstraintT = text "Constraint" pprParendType (SigT ty k) = parens (ppr ty <+> text "::" <+> ppr k) diff --git a/testsuite/tests/th/T13887.hs b/testsuite/tests/th/T13887.hs new file mode 100644 index 0000000..8687447 --- /dev/null +++ b/testsuite/tests/th/T13887.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE TemplateHaskell #-} +module Main where + +import Data.Proxy +import GHC.Generics +import Language.Haskell.TH + +main :: IO () +main = do + putStrLn $([t| Proxy (:*:) |] >>= stringE . pprint) + putStrLn $([t| Proxy '(:*:) |] >>= stringE . pprint) + putStrLn $([t| Proxy '(:) |] >>= stringE . pprint) diff --git a/testsuite/tests/th/T13887.stdout b/testsuite/tests/th/T13887.stdout new file mode 100644 index 0000000..48845be --- /dev/null +++ b/testsuite/tests/th/T13887.stdout @@ -0,0 +1,3 @@ +Data.Proxy.Proxy (GHC.Generics.:*:) +Data.Proxy.Proxy '(GHC.Generics.:*:) +Data.Proxy.Proxy '(GHC.Types.:) diff --git a/testsuite/tests/th/TH_PromotedList.stderr b/testsuite/tests/th/TH_PromotedList.stderr index 8a6422f..fde888f 100644 --- a/testsuite/tests/th/TH_PromotedList.stderr +++ b/testsuite/tests/th/TH_PromotedList.stderr @@ -1,3 +1,3 @@ -TH_PromotedList.hs:11:3: Warning: - (':) GHC.Types.Int ((':) GHC.Types.Bool '[]) +TH_PromotedList.hs:11:3: warning: + '(:) GHC.Types.Int ('(:) GHC.Types.Bool '[]) diff --git a/testsuite/tests/th/TH_RichKinds2.stderr b/testsuite/tests/th/TH_RichKinds2.stderr index 1182929..6b06622 100644 --- a/testsuite/tests/th/TH_RichKinds2.stderr +++ b/testsuite/tests/th/TH_RichKinds2.stderr @@ -5,5 +5,6 @@ TH_RichKinds2.hs:24:4: warning: SJust_4 :: (s_5 a_6) -> SMaybe_0 s_5 ('GHC.Base.Just a_6) type instance TH_RichKinds2.Map f_7 '[] = '[] type instance TH_RichKinds2.Map f_8 - ('GHC.Types.: h_9 t_10) = 'GHC.Types.: (f_8 h_9) - (TH_RichKinds2.Map f_8 t_10) + ('(GHC.Types.:) h_9 t_10) = '(GHC.Types.:) (f_8 h_9) + (TH_RichKinds2.Map f_8 + t_10) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 3db9857..29a6334 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -391,4 +391,5 @@ test('T13781', normal, compile, ['-v0']) test('T13782', normal, compile, ['']) test('T13837', normal, compile_fail, ['-v0 -dsuppress-uniques']) test('T13856', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques']) +test('T13887', normal, compile_and_run, ['-v0']) test('T13968', normal, compile_fail, ['-v0']) From git at git.haskell.org Sun Jul 30 13:45:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Jul 2017 13:45:37 +0000 (UTC) Subject: [commit: ghc] master: Add haddock markup (f2c12c3) Message-ID: <20170730134537.E055E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f2c12c391e8c855b208bb9b99d85bbf56b9ebbae/ghc >--------------------------------------------------------------- commit f2c12c391e8c855b208bb9b99d85bbf56b9ebbae Author: Gabor Greif Date: Fri Jul 28 21:09:03 2017 +0200 Add haddock markup >--------------------------------------------------------------- f2c12c391e8c855b208bb9b99d85bbf56b9ebbae compiler/simplStg/StgCse.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/simplStg/StgCse.hs b/compiler/simplStg/StgCse.hs index ac8e820..f3e781b 100644 --- a/compiler/simplStg/StgCse.hs +++ b/compiler/simplStg/StgCse.hs @@ -137,7 +137,7 @@ data CseEnv = CseEnv -- * If we remove `let x = Con z` because `let y = Con z` is in scope, -- we note this here as x ↦ y. , ce_bndrMap :: IdEnv OutId - -- If we come across a case expression case x as b of … with a trivial + -- ^ If we come across a case expression case x as b of … with a trivial -- binder, we add b ↦ x to this. -- This map is *only* used when looking something up in the ce_conAppMap. -- See Note [Trivial case scrutinee] From git at git.haskell.org Sun Jul 30 13:45:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Jul 2017 13:45:40 +0000 (UTC) Subject: [commit: ghc] master: Typofixes [ci skip] (9699286) Message-ID: <20170730134540.A0DD23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/969928602aa7b23bcaffe0dbfa885ffce87cea02/ghc >--------------------------------------------------------------- commit 969928602aa7b23bcaffe0dbfa885ffce87cea02 Author: Gabor Greif Date: Fri Jul 28 20:36:59 2017 +0200 Typofixes [ci skip] >--------------------------------------------------------------- 969928602aa7b23bcaffe0dbfa885ffce87cea02 compiler/basicTypes/Var.hs | 2 +- compiler/simplStg/StgCse.hs | 8 ++++---- testsuite/tests/dependent/should_fail/T13135.hs | 2 +- 3 files changed, 6 insertions(+), 6 deletions(-) diff --git a/compiler/basicTypes/Var.hs b/compiler/basicTypes/Var.hs index 58e8d52..9a39e29 100644 --- a/compiler/basicTypes/Var.hs +++ b/compiler/basicTypes/Var.hs @@ -159,7 +159,7 @@ type TyCoVar = Id -- Type, *or* coercion variable {- Many passes apply a substitution, and it's very handy to have type - synonyms to remind us whether or not the subsitution has been applied -} + synonyms to remind us whether or not the substitution has been applied -} type InVar = Var type InTyVar = TyVar diff --git a/compiler/simplStg/StgCse.hs b/compiler/simplStg/StgCse.hs index 6bd6adc..ac8e820 100644 --- a/compiler/simplStg/StgCse.hs +++ b/compiler/simplStg/StgCse.hs @@ -5,9 +5,9 @@ Note [CSE for Stg] ~~~~~~~~~~~~~~~~~~ This module implements a simple common subexpression elimination pass for STG. This is useful because there are expressions that we want to common up (because -they are operational equivalent), but that we cannot common up in Core, because +they are operationally equivalent), but that we cannot common up in Core, because their types differ. -This was original reported as #9291. +This was originally reported as #9291. There are two types of common code occurrences that we aim for, see note [Case 1: CSEing allocated closures] and @@ -217,7 +217,7 @@ substVar env id = fromMaybe id $ lookupVarEnv (ce_subst env) id -- Functions to enter binders --- This is much simpler than the requivalent code in CoreSubst: +-- This is much simpler than the equivalent code in CoreSubst: -- * We do not substitute type variables, and -- * There is nothing relevant in IdInfo at this stage -- that needs substitutions. @@ -438,7 +438,7 @@ we first replace v with r2. Next we want to replace Right r2 with r1. But the ce_conAppMap contains Right a! Therefore, we add r1 ↦ x to ce_bndrMap when analysing the outer case, and use -this subsitution before looking Right r2 up in ce_conAppMap, and everything +this substitution before looking Right r2 up in ce_conAppMap, and everything works out. Note [Free variables of an StgClosure] diff --git a/testsuite/tests/dependent/should_fail/T13135.hs b/testsuite/tests/dependent/should_fail/T13135.hs index c39b3f5..772ac78 100644 --- a/testsuite/tests/dependent/should_fail/T13135.hs +++ b/testsuite/tests/dependent/should_fail/T13135.hs @@ -62,7 +62,7 @@ arrLen = smartSym sym where -{- The original bug was a familure to subsitute +{- The original bug was a failure to substitute properly during type-function improvement. -------------------------------------- From git at git.haskell.org Sun Jul 30 13:51:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Jul 2017 13:51:02 +0000 (UTC) Subject: [commit: ghc] branch 'wip/cross-constr-cse' created Message-ID: <20170730135102.1EF343A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/cross-constr-cse Referencing: 16589a6ee13cc9816f7d6b78880af3bbae10e6f2 From git at git.haskell.org Sun Jul 30 13:51:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Jul 2017 13:51:05 +0000 (UTC) Subject: [commit: ghc] wip/cross-constr-cse: enable more tests (9a7668f) Message-ID: <20170730135105.23AEF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cross-constr-cse Link : http://ghc.haskell.org/trac/ghc/changeset/9a7668fe5668795767dedc599a8510bbe7b63967/ghc >--------------------------------------------------------------- commit 9a7668fe5668795767dedc599a8510bbe7b63967 Author: Gabor Greif Date: Sat Jul 29 17:36:57 2017 +0200 enable more tests >--------------------------------------------------------------- 9a7668fe5668795767dedc599a8510bbe7b63967 testsuite/tests/simplStg/should_run/T13861.hs | 31 +++++++++++++++-------- testsuite/tests/simplStg/should_run/T13861.stdout | 8 ++++++ 2 files changed, 28 insertions(+), 11 deletions(-) diff --git a/testsuite/tests/simplStg/should_run/T13861.hs b/testsuite/tests/simplStg/should_run/T13861.hs index 90a5d67..89b9318 100644 --- a/testsuite/tests/simplStg/should_run/T13861.hs +++ b/testsuite/tests/simplStg/should_run/T13861.hs @@ -18,20 +18,26 @@ foo' (R x) = Just x foo' _ = Nothing {-# NOINLINE foo' #-} +baz :: [a] -> Maybe a +baz [] = Nothing +baz [a] = Just a +baz _ = Nothing +{-# NOINLINE baz #-} -nested :: Either Int (Either Int a) -> Either Bool (Either Bool a) -nested (Right (Right x)) = Right (Right x) + +nested :: Either Int (Either Int a) -> Either Bool (Maybe a) +nested (Right (Right x)) = Right (Just x) nested _ = Left True {-# NOINLINE nested #-} -- CSE in a recursive group -data Tree x = T x (Either Int (Tree x)) (Either Bool (Tree x)) +data Tree x = T x (Either Int (Tree x)) (Maybe (Tree x)) rec1 :: x -> Tree x rec1 x = let t = T x r1 r2 r1 = Right t - r2 = Right t + r2 = Just t in t {-# NOINLINE rec1 #-} @@ -51,13 +57,16 @@ test x = do (same $! r1) $! r3 let (r30, r31) = (R 'l', foo' r30) (same $! r30) $! r31 - -- let (r4,_) = bar r1 - -- let r5 = nested r4 - -- (same $! r4) $! r5 - -- let (T _ r6 r7) = rec1 x - -- (same $! r6) $! r7 - -- let s1@(S _ s2) = rec2 x - -- (same $! s1) $! s2 + + let (r40, r41) = (['l'], baz r40) + (same $! r40) $! r41 + let (r4,_) = bar r1 + let r5 = nested r4 + (same $! r4) $! r5 + let (T _ r6 r7) = rec1 x + (same $! r6) $! r7 + let s1@(S _ s2) = rec2 x + (same $! s1) $! s2 case r3 of Just b -> print ("YAY", b) Nothing -> print "BAD" diff --git a/testsuite/tests/simplStg/should_run/T13861.stdout b/testsuite/tests/simplStg/should_run/T13861.stdout new file mode 100644 index 0000000..3127164 --- /dev/null +++ b/testsuite/tests/simplStg/should_run/T13861.stdout @@ -0,0 +1,8 @@ +yes +yes +no +no +yes +yes +no +("YAY","foo") From git at git.haskell.org Sun Jul 30 13:51:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Jul 2017 13:51:07 +0000 (UTC) Subject: [commit: ghc] wip/cross-constr-cse: WIP: first working version (d519bbb) Message-ID: <20170730135107.D4D113A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cross-constr-cse Link : http://ghc.haskell.org/trac/ghc/changeset/d519bbb9cbde7d0cb80ede18451745133d50376a/ghc >--------------------------------------------------------------- commit d519bbb9cbde7d0cb80ede18451745133d50376a Author: Gabor Greif Date: Sat Jul 29 16:42:37 2017 +0200 WIP: first working version >--------------------------------------------------------------- d519bbb9cbde7d0cb80ede18451745133d50376a compiler/simplStg/StgCse.hs | 50 +++++++++++++++++++++++++++++++++++++-------- 1 file changed, 42 insertions(+), 8 deletions(-) diff --git a/compiler/simplStg/StgCse.hs b/compiler/simplStg/StgCse.hs index f3e781b..38b7262 100644 --- a/compiler/simplStg/StgCse.hs +++ b/compiler/simplStg/StgCse.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeFamilies, ViewPatterns, LambdaCase #-} {-| Note [CSE for Stg] @@ -81,6 +81,9 @@ import Data.Maybe (fromMaybe) import TrieMap import NameEnv import Control.Monad( (>=>) ) +import Data.Function (on) +import Name (NamedThing (..), getOccString, mkFCallName) +import Unique(Uniquable(..), mkUniqueGrimily) -------------- -- The Trie -- @@ -108,9 +111,40 @@ instance TrieMap StgArgMap where newtype ConAppMap a = CAM { un_cam :: DNameEnv (ListMap StgArgMap a) } +newtype LaxDataCon = Lax DataCon + +unLax (Lax dc) = dc +{- +instance Eq LaxDataCon where +-- (==) = (==) `on` dataConTag . unLax + Lax dcl == Lax dcr | dcl == dcr = True + | True {- ((==) `on` dataConTag) dcl dcr + && ((&&) `on` isVanillaDataCon) dcl dcr + && ((==) `on` length {- FIXME? -} . dataConOrigArgTys) dcl dcr -} + = error $ show (getOccString dcl, getOccString dcr) -- True + | otherwise = False +-} +{- +instance Ord LaxDataCon where + l@(Lax dcl) `compare` r@(Lax dcr) = if l == r then EQ else dcl `compare` dcr +-} + +instance NamedThing LaxDataCon where + --getName = getName . unLax + getName (Lax dc) | isVanillaDataCon dc && not hasStrict && not unpacked = mkFCallName uniq "%%%HALLO" + where uniq = mkUniqueGrimily . negate $ dataConTag dc * 10000 + length (dataConOrigArgTys dc) + hasStrict = any (\case HsLazy -> False; _ -> True) (dataConImplBangs dc) + unpacked = isUnboxedTupleCon dc || isUnboxedSumCon dc + getName (Lax dc) = getName dc + +instance Uniquable LaxDataCon where + getUnique = error "Uniquable" -- mkUniqueGrimily . dataConTag . unLax + + instance TrieMap ConAppMap where - type Key ConAppMap = (DataCon, [StgArg]) + type Key ConAppMap = (LaxDataCon, [StgArg]) emptyTM = CAM emptyTM + --lookupTM ((getOccString -> "Just"), args) = error (show ("args", length args)) lookupTM (dataCon, args) = un_cam >.> lkDNamed dataCon >=> lookupTM args alterTM (dataCon, args) f m = m { un_cam = un_cam m |> xtDNamed dataCon |>> alterTM args f } @@ -177,13 +211,13 @@ initEnv in_scope = CseEnv , ce_in_scope = in_scope } -envLookup :: DataCon -> [OutStgArg] -> CseEnv -> Maybe OutId +envLookup :: LaxDataCon -> [OutStgArg] -> CseEnv -> Maybe OutId envLookup dataCon args env = lookupTM (dataCon, args') (ce_conAppMap env) where args' = map go args -- See Note [Trivial case scrutinee] go (StgVarArg v ) = StgVarArg (fromMaybe v $ lookupVarEnv (ce_bndrMap env) v) go (StgLitArg lit) = StgLitArg lit -addDataCon :: OutId -> DataCon -> [OutStgArg] -> CseEnv -> CseEnv +addDataCon :: OutId -> LaxDataCon -> [OutStgArg] -> CseEnv -> CseEnv -- do not bother with nullary data constructors, they are static anyways addDataCon _ _ [] env = env addDataCon bndr dataCon args env = env { ce_conAppMap = new_env } @@ -306,7 +340,7 @@ stgCseExpr env (StgCase scrut bndr ty alts) -- A constructor application. -- To be removed by a variable use when found in the CSE environment stgCseExpr env (StgConApp dataCon args tys) - | Just bndr' <- envLookup dataCon args' env + | Just bndr' <- envLookup (Lax dataCon) args' env = StgApp bndr' [] | otherwise = StgConApp dataCon args' tys @@ -330,7 +364,7 @@ stgCseExpr env (StgLetNoEscape binds body) stgCseAlt :: CseEnv -> OutId -> InStgAlt -> OutStgAlt stgCseAlt env case_bndr (DataAlt dataCon, args, rhs) = let (env1, args') = substBndrs env args - env2 = addDataCon case_bndr dataCon (map StgVarArg args') env1 + env2 = addDataCon case_bndr (Lax dataCon) (map StgVarArg args') env1 -- see note [Case 2: CSEing case binders] rhs' = stgCseExpr env2 rhs in (DataAlt dataCon, args', rhs') @@ -365,11 +399,11 @@ stgCsePairs env0 ((b,e):pairs) -- If it is an constructor application, either short-cut it or extend the environment stgCseRhs :: CseEnv -> OutId -> InStgRhs -> (Maybe (OutId, OutStgRhs), CseEnv) stgCseRhs env bndr (StgRhsCon ccs dataCon args) - | Just other_bndr <- envLookup dataCon args' env + | Just other_bndr <- envLookup (Lax dataCon) args' env = let env' = addSubst bndr other_bndr env in (Nothing, env') | otherwise - = let env' = addDataCon bndr dataCon args' env + = let env' = addDataCon bndr (Lax dataCon) args' env -- see note [Case 1: CSEing allocated closures] pair = (bndr, StgRhsCon ccs dataCon args') in (Just pair, env') From git at git.haskell.org Sun Jul 30 13:51:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Jul 2017 13:51:10 +0000 (UTC) Subject: [commit: ghc] wip/cross-constr-cse: test Right -> Just (5a3aa10) Message-ID: <20170730135110.E2A623A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cross-constr-cse Link : http://ghc.haskell.org/trac/ghc/changeset/5a3aa10c1fcd99b510b93458d2776e0599b0e3da/ghc >--------------------------------------------------------------- commit 5a3aa10c1fcd99b510b93458d2776e0599b0e3da Author: Gabor Greif Date: Sat Jul 29 16:43:04 2017 +0200 test Right -> Just >--------------------------------------------------------------- 5a3aa10c1fcd99b510b93458d2776e0599b0e3da .../simplStg/should_run/{T9291.hs => T13861.hs} | 39 ++++++++++++++-------- 1 file changed, 26 insertions(+), 13 deletions(-) diff --git a/testsuite/tests/simplStg/should_run/T9291.hs b/testsuite/tests/simplStg/should_run/T13861.hs similarity index 59% copy from testsuite/tests/simplStg/should_run/T9291.hs copy to testsuite/tests/simplStg/should_run/T13861.hs index db2ce75..90a5d67 100644 --- a/testsuite/tests/simplStg/should_run/T9291.hs +++ b/testsuite/tests/simplStg/should_run/T13861.hs @@ -1,16 +1,24 @@ -{-# LANGUAGE MagicHash #-} +{-# LANGUAGE MagicHash, BangPatterns #-} import GHC.Exts import Unsafe.Coerce -foo :: Either Int a -> Either Bool a -foo (Right x) = Right x -foo _ = Left True +foo :: Either Int a -> Maybe a +foo (Right x) = Just x +foo _ = Nothing {-# NOINLINE foo #-} -bar :: a -> (Either Int a, Either Bool a) -bar x = (Right x, Right x) +bar :: a -> (Either Int a, Maybe a) +bar x = (Right x, Just x) {-# NOINLINE bar #-} +data E a b = L a | R !b + +foo' :: E Int a -> Maybe a +foo' (R x) = Just x +foo' _ = Nothing +{-# NOINLINE foo' #-} + + nested :: Either Int (Either Int a) -> Either Bool (Either Bool a) nested (Right (Right x)) = Right (Right x) nested _ = Left True @@ -41,13 +49,18 @@ test x = do (same $! r1) $! r2 let r3 = foo r1 (same $! r1) $! r3 - let (r4,_) = bar r1 - let r5 = nested r4 - (same $! r4) $! r5 - let (T _ r6 r7) = rec1 x - (same $! r6) $! r7 - let s1@(S _ s2) = rec2 x - (same $! s1) $! s2 + let (r30, r31) = (R 'l', foo' r30) + (same $! r30) $! r31 + -- let (r4,_) = bar r1 + -- let r5 = nested r4 + -- (same $! r4) $! r5 + -- let (T _ r6 r7) = rec1 x + -- (same $! r6) $! r7 + -- let s1@(S _ s2) = rec2 x + -- (same $! s1) $! s2 + case r3 of + Just b -> print ("YAY", b) + Nothing -> print "BAD" {-# NOINLINE test #-} main = test "foo" From git at git.haskell.org Sun Jul 30 13:51:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Jul 2017 13:51:13 +0000 (UTC) Subject: [commit: ghc] wip/cross-constr-cse: Add T13861 (49d702f) Message-ID: <20170730135113.9E4B43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cross-constr-cse Link : http://ghc.haskell.org/trac/ghc/changeset/49d702f3cf5d5157d38fe808bf2024767d26c2e3/ghc >--------------------------------------------------------------- commit 49d702f3cf5d5157d38fe808bf2024767d26c2e3 Author: Gabor Greif Date: Sat Jul 29 22:11:01 2017 +0200 Add T13861 >--------------------------------------------------------------- 49d702f3cf5d5157d38fe808bf2024767d26c2e3 testsuite/tests/simplStg/should_run/all.T | 2 ++ 1 file changed, 2 insertions(+) diff --git a/testsuite/tests/simplStg/should_run/all.T b/testsuite/tests/simplStg/should_run/all.T index d3aa937..6ca2e6b 100644 --- a/testsuite/tests/simplStg/should_run/all.T +++ b/testsuite/tests/simplStg/should_run/all.T @@ -10,6 +10,8 @@ def f( name, opts ): setTestOpts(f) test('T9291', normal, compile_and_run, ['']) +test('T13861', normal, compile_and_run, ['']) + test('T13536', normal, compile_and_run, ['']) test('T13536a', From git at git.haskell.org Sun Jul 30 13:51:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Jul 2017 13:51:16 +0000 (UTC) Subject: [commit: ghc] wip/cross-constr-cse: clean up (649c50a) Message-ID: <20170730135116.679E93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cross-constr-cse Link : http://ghc.haskell.org/trac/ghc/changeset/649c50aef03497d636fd07d2c6ac5a4ee9d13816/ghc >--------------------------------------------------------------- commit 649c50aef03497d636fd07d2c6ac5a4ee9d13816 Author: Gabor Greif Date: Sat Jul 29 22:21:53 2017 +0200 clean up >--------------------------------------------------------------- 649c50aef03497d636fd07d2c6ac5a4ee9d13816 compiler/simplStg/StgCse.hs | 34 ++++++---------------------------- 1 file changed, 6 insertions(+), 28 deletions(-) diff --git a/compiler/simplStg/StgCse.hs b/compiler/simplStg/StgCse.hs index 38b7262..c1ec54b 100644 --- a/compiler/simplStg/StgCse.hs +++ b/compiler/simplStg/StgCse.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE TypeFamilies, ViewPatterns, LambdaCase #-} +{-# LANGUAGE TypeFamilies, LambdaCase #-} {-| Note [CSE for Stg] @@ -16,7 +16,7 @@ note [Case 2: CSEing case binders] below. Note [Case 1: CSEing allocated closures] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -The fist kind of CSE opportunity we aim for is generated by this Haskell code: +The first kind of CSE opportunity we aim for is generated by this Haskell code: bar :: a -> (Either Int a, Either Bool a) bar x = (Right x, Right x) @@ -81,16 +81,15 @@ import Data.Maybe (fromMaybe) import TrieMap import NameEnv import Control.Monad( (>=>) ) -import Data.Function (on) -import Name (NamedThing (..), getOccString, mkFCallName) -import Unique(Uniquable(..), mkUniqueGrimily) +import Name (NamedThing (..), mkFCallName) +import Unique (mkUniqueGrimily) -------------- -- The Trie -- -------------- -- A lookup trie for data constructor applications, i.e. --- keys of type `(DataCon, [StgArg])`, following the patterns in TrieMap. +-- keys of type `(LaxDataCon, [StgArg])`, following the patterns in TrieMap. data StgArgMap a = SAM { sam_var :: DVarEnv a @@ -113,38 +112,17 @@ newtype ConAppMap a = CAM { un_cam :: DNameEnv (ListMap StgArgMap a) } newtype LaxDataCon = Lax DataCon -unLax (Lax dc) = dc -{- -instance Eq LaxDataCon where --- (==) = (==) `on` dataConTag . unLax - Lax dcl == Lax dcr | dcl == dcr = True - | True {- ((==) `on` dataConTag) dcl dcr - && ((&&) `on` isVanillaDataCon) dcl dcr - && ((==) `on` length {- FIXME? -} . dataConOrigArgTys) dcl dcr -} - = error $ show (getOccString dcl, getOccString dcr) -- True - | otherwise = False --} -{- -instance Ord LaxDataCon where - l@(Lax dcl) `compare` r@(Lax dcr) = if l == r then EQ else dcl `compare` dcr --} - instance NamedThing LaxDataCon where - --getName = getName . unLax - getName (Lax dc) | isVanillaDataCon dc && not hasStrict && not unpacked = mkFCallName uniq "%%%HALLO" + getName (Lax dc) | isVanillaDataCon dc && not hasStrict && not unpacked = mkFCallName uniq "%%%HALLO" -- FIXME where uniq = mkUniqueGrimily . negate $ dataConTag dc * 10000 + length (dataConOrigArgTys dc) hasStrict = any (\case HsLazy -> False; _ -> True) (dataConImplBangs dc) unpacked = isUnboxedTupleCon dc || isUnboxedSumCon dc getName (Lax dc) = getName dc -instance Uniquable LaxDataCon where - getUnique = error "Uniquable" -- mkUniqueGrimily . dataConTag . unLax - instance TrieMap ConAppMap where type Key ConAppMap = (LaxDataCon, [StgArg]) emptyTM = CAM emptyTM - --lookupTM ((getOccString -> "Just"), args) = error (show ("args", length args)) lookupTM (dataCon, args) = un_cam >.> lkDNamed dataCon >=> lookupTM args alterTM (dataCon, args) f m = m { un_cam = un_cam m |> xtDNamed dataCon |>> alterTM args f } From git at git.haskell.org Sun Jul 30 13:51:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Jul 2017 13:51:19 +0000 (UTC) Subject: [commit: ghc] wip/cross-constr-cse: more to fix (fd301b6) Message-ID: <20170730135119.29E6D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cross-constr-cse Link : http://ghc.haskell.org/trac/ghc/changeset/fd301b69096415f7bb01f95c2ea2d22f12d4991c/ghc >--------------------------------------------------------------- commit fd301b69096415f7bb01f95c2ea2d22f12d4991c Author: Gabor Greif Date: Sat Jul 29 23:05:24 2017 +0200 more to fix >--------------------------------------------------------------- fd301b69096415f7bb01f95c2ea2d22f12d4991c compiler/simplStg/StgCse.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/simplStg/StgCse.hs b/compiler/simplStg/StgCse.hs index c1ec54b..ee89137 100644 --- a/compiler/simplStg/StgCse.hs +++ b/compiler/simplStg/StgCse.hs @@ -113,8 +113,8 @@ newtype ConAppMap a = CAM { un_cam :: DNameEnv (ListMap StgArgMap a) } newtype LaxDataCon = Lax DataCon instance NamedThing LaxDataCon where - getName (Lax dc) | isVanillaDataCon dc && not hasStrict && not unpacked = mkFCallName uniq "%%%HALLO" -- FIXME - where uniq = mkUniqueGrimily . negate $ dataConTag dc * 10000 + length (dataConOrigArgTys dc) + getName (Lax dc) | isVanillaDataCon dc && not hasStrict && not unpacked = mkFCallName uniq "" -- FIXME: is there a better way? + where uniq = mkUniqueGrimily . negate $ dataConTag dc * 1048576 + length (dataConOrigArgTys dc) -- FIXME hasStrict = any (\case HsLazy -> False; _ -> True) (dataConImplBangs dc) unpacked = isUnboxedTupleCon dc || isUnboxedSumCon dc getName (Lax dc) = getName dc From git at git.haskell.org Sun Jul 30 13:51:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Jul 2017 13:51:21 +0000 (UTC) Subject: [commit: ghc] wip/cross-constr-cse: WIP: debugging (16589a6) Message-ID: <20170730135121.E4C3E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cross-constr-cse Link : http://ghc.haskell.org/trac/ghc/changeset/16589a6ee13cc9816f7d6b78880af3bbae10e6f2/ghc >--------------------------------------------------------------- commit 16589a6ee13cc9816f7d6b78880af3bbae10e6f2 Author: Gabor Greif Date: Sun Jul 30 13:22:28 2017 +0200 WIP: debugging >--------------------------------------------------------------- 16589a6ee13cc9816f7d6b78880af3bbae10e6f2 compiler/simplStg/StgCse.hs | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/compiler/simplStg/StgCse.hs b/compiler/simplStg/StgCse.hs index ee89137..c4dabb3 100644 --- a/compiler/simplStg/StgCse.hs +++ b/compiler/simplStg/StgCse.hs @@ -113,7 +113,7 @@ newtype ConAppMap a = CAM { un_cam :: DNameEnv (ListMap StgArgMap a) } newtype LaxDataCon = Lax DataCon instance NamedThing LaxDataCon where - getName (Lax dc) | isVanillaDataCon dc && not hasStrict && not unpacked = mkFCallName uniq "" -- FIXME: is there a better way? + getName (Lax dc) | False && isVanillaDataCon dc && not hasStrict && not unpacked = mkFCallName uniq "" -- FIXME: is there a better way? where uniq = mkUniqueGrimily . negate $ dataConTag dc * 1048576 + length (dataConOrigArgTys dc) -- FIXME hasStrict = any (\case HsLazy -> False; _ -> True) (dataConImplBangs dc) unpacked = isUnboxedTupleCon dc || isUnboxedSumCon dc @@ -123,12 +123,16 @@ instance NamedThing LaxDataCon where instance TrieMap ConAppMap where type Key ConAppMap = (LaxDataCon, [StgArg]) emptyTM = CAM emptyTM + lookupTM (dataCon, args) | traceLookup dataCon = undefined lookupTM (dataCon, args) = un_cam >.> lkDNamed dataCon >=> lookupTM args alterTM (dataCon, args) f m = m { un_cam = un_cam m |> xtDNamed dataCon |>> alterTM args f } foldTM k = un_cam >.> foldTM (foldTM k) mapTM f = un_cam >.> mapTM (mapTM f) >.> CAM +traceLookup (Lax dc) = pprTrace "lookupTM" (ppr dc) False +{-# NOINLINE traceLookup #-} + ----------------- -- The CSE Env -- ----------------- @@ -197,7 +201,9 @@ envLookup dataCon args env = lookupTM (dataCon, args') (ce_conAppMap env) addDataCon :: OutId -> LaxDataCon -> [OutStgArg] -> CseEnv -> CseEnv -- do not bother with nullary data constructors, they are static anyways -addDataCon _ _ [] env = env +addDataCon bndr dataCon [] env = env { ce_conAppMap = new_env } + where new_env = alterTM (dataCon, []) (\case Nothing -> pure bndr; p -> p) (ce_conAppMap env) +--addDataCon _ _ [] env = env addDataCon bndr dataCon args env = env { ce_conAppMap = new_env } where new_env = insertTM (dataCon, args) bndr (ce_conAppMap env) From git at git.haskell.org Sun Jul 30 15:47:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Jul 2017 15:47:53 +0000 (UTC) Subject: [commit: ghc] wip/cross-constr-cse: suppress some warnings for now and enable the optsn (acaaed1) Message-ID: <20170730154753.C4CBB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cross-constr-cse Link : http://ghc.haskell.org/trac/ghc/changeset/acaaed1101f190d0fb8d5ff4d25efe98fad966fa/ghc >--------------------------------------------------------------- commit acaaed1101f190d0fb8d5ff4d25efe98fad966fa Author: Gabor Greif Date: Sun Jul 30 17:47:09 2017 +0200 suppress some warnings for now and enable the optsn >--------------------------------------------------------------- acaaed1101f190d0fb8d5ff4d25efe98fad966fa compiler/simplStg/StgCse.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/simplStg/StgCse.hs b/compiler/simplStg/StgCse.hs index c4dabb3..91a96ec 100644 --- a/compiler/simplStg/StgCse.hs +++ b/compiler/simplStg/StgCse.hs @@ -1,4 +1,5 @@ {-# LANGUAGE TypeFamilies, LambdaCase #-} +{-# OPTIONS_GHC -Wno-unused-matches -Wno-missing-signatures #-} {-| Note [CSE for Stg] @@ -113,7 +114,7 @@ newtype ConAppMap a = CAM { un_cam :: DNameEnv (ListMap StgArgMap a) } newtype LaxDataCon = Lax DataCon instance NamedThing LaxDataCon where - getName (Lax dc) | False && isVanillaDataCon dc && not hasStrict && not unpacked = mkFCallName uniq "" -- FIXME: is there a better way? + getName (Lax dc) | isVanillaDataCon dc && not hasStrict && not unpacked = mkFCallName uniq "" -- FIXME: is there a better way? where uniq = mkUniqueGrimily . negate $ dataConTag dc * 1048576 + length (dataConOrigArgTys dc) -- FIXME hasStrict = any (\case HsLazy -> False; _ -> True) (dataConImplBangs dc) unpacked = isUnboxedTupleCon dc || isUnboxedSumCon dc From git at git.haskell.org Sun Jul 30 16:15:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Jul 2017 16:15:42 +0000 (UTC) Subject: [commit: ghc] wip/cross-constr-cse: better comment out some lines that gen warnings (66d1a57) Message-ID: <20170730161542.EE24F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cross-constr-cse Link : http://ghc.haskell.org/trac/ghc/changeset/66d1a577c560dc2ca5bbcf9cda8a86df4e2f86a3/ghc >--------------------------------------------------------------- commit 66d1a577c560dc2ca5bbcf9cda8a86df4e2f86a3 Author: Gabor Greif Date: Sun Jul 30 18:15:19 2017 +0200 better comment out some lines that gen warnings >--------------------------------------------------------------- 66d1a577c560dc2ca5bbcf9cda8a86df4e2f86a3 compiler/simplStg/StgCse.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/compiler/simplStg/StgCse.hs b/compiler/simplStg/StgCse.hs index 91a96ec..6690f82 100644 --- a/compiler/simplStg/StgCse.hs +++ b/compiler/simplStg/StgCse.hs @@ -1,5 +1,4 @@ {-# LANGUAGE TypeFamilies, LambdaCase #-} -{-# OPTIONS_GHC -Wno-unused-matches -Wno-missing-signatures #-} {-| Note [CSE for Stg] @@ -124,7 +123,7 @@ instance NamedThing LaxDataCon where instance TrieMap ConAppMap where type Key ConAppMap = (LaxDataCon, [StgArg]) emptyTM = CAM emptyTM - lookupTM (dataCon, args) | traceLookup dataCon = undefined + --lookupTM (dataCon, args) | traceLookup dataCon = undefined lookupTM (dataCon, args) = un_cam >.> lkDNamed dataCon >=> lookupTM args alterTM (dataCon, args) f m = m { un_cam = un_cam m |> xtDNamed dataCon |>> alterTM args f } From git at git.haskell.org Sun Jul 30 21:22:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Jul 2017 21:22:48 +0000 (UTC) Subject: [commit: ghc] wip/cross-constr-cse: better comment out some lines that gen warnings (9460748) Message-ID: <20170730212248.B89E43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cross-constr-cse Link : http://ghc.haskell.org/trac/ghc/changeset/9460748ddf3267f9509e6a37e5c61800ac8e9127/ghc >--------------------------------------------------------------- commit 9460748ddf3267f9509e6a37e5c61800ac8e9127 Author: Gabor Greif Date: Sun Jul 30 18:15:19 2017 +0200 better comment out some lines that gen warnings >--------------------------------------------------------------- 9460748ddf3267f9509e6a37e5c61800ac8e9127 compiler/simplStg/StgCse.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/compiler/simplStg/StgCse.hs b/compiler/simplStg/StgCse.hs index 91a96ec..6d845b3 100644 --- a/compiler/simplStg/StgCse.hs +++ b/compiler/simplStg/StgCse.hs @@ -1,5 +1,4 @@ {-# LANGUAGE TypeFamilies, LambdaCase #-} -{-# OPTIONS_GHC -Wno-unused-matches -Wno-missing-signatures #-} {-| Note [CSE for Stg] @@ -124,15 +123,15 @@ instance NamedThing LaxDataCon where instance TrieMap ConAppMap where type Key ConAppMap = (LaxDataCon, [StgArg]) emptyTM = CAM emptyTM - lookupTM (dataCon, args) | traceLookup dataCon = undefined + --lookupTM (dataCon, args) | traceLookup dataCon = undefined lookupTM (dataCon, args) = un_cam >.> lkDNamed dataCon >=> lookupTM args alterTM (dataCon, args) f m = m { un_cam = un_cam m |> xtDNamed dataCon |>> alterTM args f } foldTM k = un_cam >.> foldTM (foldTM k) mapTM f = un_cam >.> mapTM (mapTM f) >.> CAM -traceLookup (Lax dc) = pprTrace "lookupTM" (ppr dc) False -{-# NOINLINE traceLookup #-} +--traceLookup (Lax dc) = pprTrace "lookupTM" (ppr dc) False +--{-# NOINLINE traceLookup #-} ----------------- -- The CSE Env -- From git at git.haskell.org Mon Jul 31 03:09:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Jul 2017 03:09:41 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix whitespace (a55cec6) Message-ID: <20170731030941.72F4D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a55cec634908a7fdb24be9afb2cc75816f0f1485/ghc >--------------------------------------------------------------- commit a55cec634908a7fdb24be9afb2cc75816f0f1485 Author: Ben Gamari Date: Sun Jul 30 23:09:03 2017 -0400 Fix whitespace >--------------------------------------------------------------- a55cec634908a7fdb24be9afb2cc75816f0f1485 Jenkinsfile | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 23b6ced..8501f87 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -315,11 +315,11 @@ def nofib(params) { stage('Run nofib') { installPkgs(['regex-compat']) sh """ - cd nofib - ${makeCmd} clean - ${makeCmd} boot - ${makeCmd} >../nofib.log 2>&1 - """ + cd nofib + ${makeCmd} clean + ${makeCmd} boot + ${makeCmd} >../nofib.log 2>&1 + """ archiveArtifacts artifacts: 'nofib.log' } } From git at git.haskell.org Mon Jul 31 03:09:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Jul 2017 03:09:44 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Bump GHC to 8.2.1 (bcdefe6) Message-ID: <20170731030944.31E6C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/bcdefe6d9bb339896659c080267441294c249874/ghc >--------------------------------------------------------------- commit bcdefe6d9bb339896659c080267441294c249874 Author: Ben Gamari Date: Sun Jul 30 23:09:12 2017 -0400 Bump GHC to 8.2.1 >--------------------------------------------------------------- bcdefe6d9bb339896659c080267441294c249874 Jenkinsfile | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 8501f87..7eac8ff 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -119,11 +119,11 @@ def withMingw(String msystem, Closure f) { if (msystem == 'MINGW32') { prefix = "${msysRoot}\\mingw32" carch = 'i686' - ghcPath = "${home}/ghc-8.0.1-i386/bin" + ghcPath = "${home}/ghc-8.2.1-i386/bin" } else if (msystem == 'MINGW64') { prefix = "${msysRoot}\\mingw64" carch = 'x86_64' - ghcPath = "${home}/ghc-8.0.2-x86_64/bin" + ghcPath = "${home}/ghc-8.2.1-x86_64/bin" } else { fail } From git at git.haskell.org Mon Jul 31 04:41:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Jul 2017 04:41:41 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix junit output path (4afec48) Message-ID: <20170731044141.4846F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/4afec486bf36288929d5f8a0a3ead9fdd7291418/ghc >--------------------------------------------------------------- commit 4afec486bf36288929d5f8a0a3ead9fdd7291418 Author: Ben Gamari Date: Mon Jul 31 00:41:25 2017 -0400 Fix junit output path >--------------------------------------------------------------- 4afec486bf36288929d5f8a0a3ead9fdd7291418 Jenkinsfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index 7eac8ff..c86060c 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -302,7 +302,7 @@ def testGhc(params) { if (params.nightly) { target = 'slowtest' } - sh "${makeCmd} -Ctestsuite/tests LOCAL=0 BINDIST=YES THREADS=${env.THREADS} TEST_HC=\"${testGhc}\" JUNIT_FILE=testsuite.xml ${target}" + sh "${makeCmd} -Ctestsuite/tests LOCAL=0 BINDIST=YES THREADS=${env.THREADS} TEST_HC=\"${testGhc}\" JUNIT_FILE=../../testsuite.xml ${target}" junit 'testsuite.xml' } } From git at git.haskell.org Mon Jul 31 04:51:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Jul 2017 04:51:19 +0000 (UTC) Subject: [commit: ghc] master: Allow Windows to set blank environment variables (49e334c) Message-ID: <20170731045119.D451B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/49e334c8ea98cd5ecc81cfe10827538182815723/ghc >--------------------------------------------------------------- commit 49e334c8ea98cd5ecc81cfe10827538182815723 Author: Habib Alamin Date: Mon Jul 31 05:48:43 2017 +0100 Allow Windows to set blank environment variables Test Plan: ./validate on harbormaster Reviewers: austin, hvr, bgamari, erikd, Phyx Reviewed By: Phyx Subscribers: Phyx, rwbarton, thomie GHC Trac Issues: #12494 Differential Revision: https://phabricator.haskell.org/D3726 >--------------------------------------------------------------- 49e334c8ea98cd5ecc81cfe10827538182815723 docs/users_guide/8.4.1-notes.rst | 6 + libraries/base/System/Environment.hs | 10 +- libraries/base/System/Environment/Blank.hsc | 196 ++++++++++++++++++++++++++++ libraries/base/base.cabal | 1 + libraries/base/tests/T12494.hs | 36 +++++ libraries/base/tests/T12494.stdout | 8 ++ libraries/base/tests/all.T | 1 + 7 files changed, 253 insertions(+), 5 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 49e334c8ea98cd5ecc81cfe10827538182815723 From git at git.haskell.org Mon Jul 31 07:14:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Jul 2017 07:14:35 +0000 (UTC) Subject: [commit: ghc] wip/cross-constr-cse: disable the nullary constr subst for now (32c1ad1) Message-ID: <20170731071435.5996D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cross-constr-cse Link : http://ghc.haskell.org/trac/ghc/changeset/32c1ad141721f842c61eeeabdbff0d6359fea1bc/ghc >--------------------------------------------------------------- commit 32c1ad141721f842c61eeeabdbff0d6359fea1bc Author: Gabor Greif Date: Mon Jul 31 09:13:10 2017 +0200 disable the nullary constr subst for now >--------------------------------------------------------------- 32c1ad141721f842c61eeeabdbff0d6359fea1bc compiler/simplStg/StgCse.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/simplStg/StgCse.hs b/compiler/simplStg/StgCse.hs index 6d845b3..e25ab91 100644 --- a/compiler/simplStg/StgCse.hs +++ b/compiler/simplStg/StgCse.hs @@ -201,9 +201,9 @@ envLookup dataCon args env = lookupTM (dataCon, args') (ce_conAppMap env) addDataCon :: OutId -> LaxDataCon -> [OutStgArg] -> CseEnv -> CseEnv -- do not bother with nullary data constructors, they are static anyways -addDataCon bndr dataCon [] env = env { ce_conAppMap = new_env } - where new_env = alterTM (dataCon, []) (\case Nothing -> pure bndr; p -> p) (ce_conAppMap env) ---addDataCon _ _ [] env = env +--addDataCon bndr dataCon [] env = env { ce_conAppMap = new_env } +-- where new_env = alterTM (dataCon, []) (\case Nothing -> pure bndr; p -> p) (ce_conAppMap env) +addDataCon _ _ [] env = env addDataCon bndr dataCon args env = env { ce_conAppMap = new_env } where new_env = insertTM (dataCon, args) bndr (ce_conAppMap env) From git at git.haskell.org Mon Jul 31 12:32:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Jul 2017 12:32:50 +0000 (UTC) Subject: [commit: ghc] master: Clarify comment about data family arities (c6d4219) Message-ID: <20170731123250.444063A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c6d4219ae46cddd63aa2b5762efaf99f815009a4/ghc >--------------------------------------------------------------- commit c6d4219ae46cddd63aa2b5762efaf99f815009a4 Author: Richard Eisenberg Date: Mon Jul 31 08:29:48 2017 -0400 Clarify comment about data family arities as requested in #14045. [skip ci] comments only >--------------------------------------------------------------- c6d4219ae46cddd63aa2b5762efaf99f815009a4 compiler/types/FamInstEnv.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs index f40dabe..b9aa439 100644 --- a/compiler/types/FamInstEnv.hs +++ b/compiler/types/FamInstEnv.hs @@ -162,6 +162,11 @@ Over-saturation is also possible: see Note [Eta reduction for data families]. Accordingly, the FamInst is never over-saturated. +Why can we allow such flexibility for data families but not for type families? +Because data families can be decomposed -- that is, they are generative and +injective. A Type family is neither and so always must be applied to all its +arguments. + Note [Eta reduction for data families] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider this From git at git.haskell.org Mon Jul 31 12:37:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Jul 2017 12:37:13 +0000 (UTC) Subject: [commit: ghc] master: Remove redundant goop (7f2dee8) Message-ID: <20170731123713.390323A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7f2dee8e5de5dbc09a7fb66ec54fd41ab4b1b2eb/ghc >--------------------------------------------------------------- commit 7f2dee8e5de5dbc09a7fb66ec54fd41ab4b1b2eb Author: Simon Peyton Jones Date: Mon Jul 31 13:25:17 2017 +0100 Remove redundant goop See comment:22 in Trac #13594 >--------------------------------------------------------------- 7f2dee8e5de5dbc09a7fb66ec54fd41ab4b1b2eb compiler/deSugar/Match.hs | 9 ++------- 1 file changed, 2 insertions(+), 7 deletions(-) diff --git a/compiler/deSugar/Match.hs b/compiler/deSugar/Match.hs index a870c6f..95cf40d 100644 --- a/compiler/deSugar/Match.hs +++ b/compiler/deSugar/Match.hs @@ -749,14 +749,9 @@ matchWrapper ctxt mb_scr (MG { mg_alts = L _ matches matchEquations ctxt new_vars eqns_info rhs_ty ; return (new_vars, result_expr) } where - mk_eqn_info vars (L _ (Match ctx pats _ grhss)) + mk_eqn_info vars (L _ (Match { m_pats = pats, m_grhss = grhss })) = do { dflags <- getDynFlags - ; let add_bang - | FunRhs {mc_strictness=SrcStrict} <- ctx - = pprTrace "addBang" empty addBang - | otherwise - = decideBangHood dflags - upats = map (unLoc . add_bang) pats + ; let upats = map (unLoc . decideBangHood dflags) pats dicts = toTcTypeBag (collectEvVarsPats upats) -- Only TcTyVars ; tm_cs <- genCaseTmCs2 mb_scr upats vars ; match_result <- addDictsDs dicts $ -- See Note [Type and Term Equality Propagation] From git at git.haskell.org Mon Jul 31 12:37:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Jul 2017 12:37:16 +0000 (UTC) Subject: [commit: ghc] master: Use field names for all uses of datacon Match (4fdc523) Message-ID: <20170731123716.298C13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4fdc523456ff6481df8d7483ae193f0c2dc2b3fe/ghc >--------------------------------------------------------------- commit 4fdc523456ff6481df8d7483ae193f0c2dc2b3fe Author: Simon Peyton Jones Date: Mon Jul 31 13:27:54 2017 +0100 Use field names for all uses of datacon Match This is refactoring only... elimiante all positional uses of the data constructor Match in favour of field names. No change in behaviour. >--------------------------------------------------------------- 4fdc523456ff6481df8d7483ae193f0c2dc2b3fe compiler/deSugar/Check.hs | 4 ++-- compiler/deSugar/Coverage.hs | 10 +++++----- compiler/deSugar/DsArrows.hs | 10 +++++----- compiler/deSugar/DsMeta.hs | 11 ++++++----- compiler/hsSyn/HsExpr.hs | 2 +- compiler/hsSyn/HsUtils.hs | 9 ++++++--- compiler/parser/RdrHsSyn.hs | 8 ++++---- compiler/rename/RnExpr.hs | 2 +- compiler/rename/RnTypes.hs | 2 +- compiler/typecheck/TcArrows.hs | 5 +++-- compiler/typecheck/TcHsSyn.hs | 5 +++-- compiler/typecheck/TcMatches.hs | 8 +++++--- 12 files changed, 42 insertions(+), 34 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 4fdc523456ff6481df8d7483ae193f0c2dc2b3fe From git at git.haskell.org Mon Jul 31 12:37:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Jul 2017 12:37:18 +0000 (UTC) Subject: [commit: ghc] master: Improve the desugaring of -XStrict (4636886) Message-ID: <20170731123718.F2AF93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/46368868dc85fc7f0c95fe88af892ad850ed7bc6/ghc >--------------------------------------------------------------- commit 46368868dc85fc7f0c95fe88af892ad850ed7bc6 Author: Simon Peyton Jones Date: Mon Jul 31 10:49:16 2017 +0100 Improve the desugaring of -XStrict Trac #14035 showed that -XStrict was generating some TERRIBLE desugarings, espcially for bindings with INLINE pragmas. Reason: with -XStrict, all AbsBinds (even for non-recursive functions) went via the general-case deguaring for AbsBinds, namely "generate a tuple and select from it", even though in this case there was only one variable in the tuple. And that in turn interacts terribly badly with INLINE pragmas. This patch cleans things up: * I killed off AbsBindsSig completely, in favour of a boolean flag abs_sig in AbsBinds. See Note [The abs_sig field of AbsBinds] This allowed me to delete lots of code; and instance-method declarations can enjoy the benefits too. (They could have before, but no one had changed them to use AbsBindsSig.) * I refactored all the AbsBinds handling in DsBinds into a new function DsBinds.dsAbsBinds. This allowed me to handle the strict case uniformly >--------------------------------------------------------------- 46368868dc85fc7f0c95fe88af892ad850ed7bc6 compiler/deSugar/Coverage.hs | 25 --- compiler/deSugar/DsBinds.hs | 236 +++++++++------------ compiler/deSugar/DsExpr.hs | 11 - compiler/deSugar/DsMeta.hs | 1 - compiler/hsSyn/HsBinds.hs | 81 ++++--- compiler/hsSyn/HsPat.hs | 2 - compiler/hsSyn/HsUtils.hs | 76 +++---- compiler/typecheck/TcBinds.hs | 32 +-- compiler/typecheck/TcClassDcl.hs | 9 +- compiler/typecheck/TcHsSyn.hs | 76 +++---- compiler/typecheck/TcInstDcls.hs | 20 +- testsuite/tests/ghc-api/T6145.hs | 2 - .../should_compile/DumpTypecheckedAst.stderr | 3 +- utils/ghctags/Main.hs | 1 - 14 files changed, 250 insertions(+), 325 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 46368868dc85fc7f0c95fe88af892ad850ed7bc6 From git at git.haskell.org Mon Jul 31 12:37:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Jul 2017 12:37:21 +0000 (UTC) Subject: [commit: ghc] master: Refactoring around FunRhs (2535a67) Message-ID: <20170731123721.C38EC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2535a6716202253df74d8190b028f85cc6d21b72/ghc >--------------------------------------------------------------- commit 2535a6716202253df74d8190b028f85cc6d21b72 Author: Simon Peyton Jones Date: Mon Jul 31 10:48:00 2017 +0100 Refactoring around FunRhs * Clarify the comments around the mc_strictness field of FunRhs * Use record field names consistently for FunRhs >--------------------------------------------------------------- 2535a6716202253df74d8190b028f85cc6d21b72 compiler/deSugar/Check.hs | 6 +++--- compiler/hsSyn/HsBinds.hs | 24 ++++++++++++++---------- compiler/hsSyn/HsExpr.hs | 9 ++++----- compiler/hsSyn/HsUtils.hs | 4 +++- compiler/parser/RdrHsSyn.hs | 20 ++++++++++++++------ compiler/rename/RnBinds.hs | 9 ++++----- compiler/typecheck/TcMatches.hs | 5 +++-- 7 files changed, 45 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 2535a6716202253df74d8190b028f85cc6d21b72 From git at git.haskell.org Mon Jul 31 12:37:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Jul 2017 12:37:24 +0000 (UTC) Subject: [commit: ghc] master: Do a bit more CSE (3ab342e) Message-ID: <20170731123724.7D8233A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3ab342eb1b82ba9218a9d7786c523b1128b2bdf1/ghc >--------------------------------------------------------------- commit 3ab342eb1b82ba9218a9d7786c523b1128b2bdf1 Author: Simon Peyton Jones Date: Mon Jul 31 11:00:33 2017 +0100 Do a bit more CSE I discovered that in let x = MkT y in ....(MKT y |> co).... we weren't CSE'ing the (MkT y). The fix is easy. >--------------------------------------------------------------- 3ab342eb1b82ba9218a9d7786c523b1128b2bdf1 compiler/simplCore/CSE.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/simplCore/CSE.hs b/compiler/simplCore/CSE.hs index 83f5ee6..ccbdf35 100644 --- a/compiler/simplCore/CSE.hs +++ b/compiler/simplCore/CSE.hs @@ -454,7 +454,7 @@ cseExpr _ (Lit lit) = Lit lit cseExpr env (Var v) = lookupSubst env v cseExpr env (App f a) = App (cseExpr env f) (tryForCSE env a) cseExpr env (Tick t e) = Tick t (cseExpr env e) -cseExpr env (Cast e co) = Cast (cseExpr env e) (substCo (csEnvSubst env) co) +cseExpr env (Cast e co) = Cast (tryForCSE env e) (substCo (csEnvSubst env) co) cseExpr env (Lam b e) = let (env', b') = addBinder env b in Lam b' (cseExpr env' e) cseExpr env (Let bind e) = let (env', bind') = cseBind NotTopLevel env bind From git at git.haskell.org Mon Jul 31 12:37:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Jul 2017 12:37:27 +0000 (UTC) Subject: [commit: ghc] master: Reject top-level banged bindings (af89d68) Message-ID: <20170731123727.998F63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/af89d6872da2e00be738e1ac541346cd84e6d141/ghc >--------------------------------------------------------------- commit af89d6872da2e00be738e1ac541346cd84e6d141 Author: Simon Peyton Jones Date: Mon Jul 31 13:22:38 2017 +0100 Reject top-level banged bindings Bizarrely, we were not rejecting !x = e Fix: * In the test in DsBinds.dsTopLHsBinds, use isBangedHsBind, not isBangedPatBind. (Indeed the latter dies altogther.) * Implement isBangedHsBind in HsUtils; be sure to handle AbsBinds All this was shown up by Trac #13594 >--------------------------------------------------------------- af89d6872da2e00be738e1ac541346cd84e6d141 compiler/deSugar/DsBinds.hs | 8 ++++---- compiler/hsSyn/HsPat.hs | 6 +----- compiler/hsSyn/HsUtils.hs | 16 ++++++++++------ testsuite/tests/typecheck/should_compile/T13594.stderr | 3 +++ testsuite/tests/typecheck/should_compile/all.T | 2 +- 5 files changed, 19 insertions(+), 16 deletions(-) diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index ae23a76..41aeb93 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -80,7 +80,7 @@ dsTopLHsBinds binds -- see Note [Strict binds checks] | not (isEmptyBag unlifted_binds) || not (isEmptyBag bang_binds) = do { mapBagM_ (top_level_err "bindings for unlifted types") unlifted_binds - ; mapBagM_ (top_level_err "strict pattern bindings") bang_binds + ; mapBagM_ (top_level_err "strict bindings") bang_binds ; return nilOL } | otherwise @@ -94,7 +94,7 @@ dsTopLHsBinds binds where unlifted_binds = filterBag (isUnliftedHsBind . unLoc) binds - bang_binds = filterBag (isBangedPatBind . unLoc) binds + bang_binds = filterBag (isBangedHsBind . unLoc) binds top_level_err desc (L loc bind) = putSrcSpanDs loc $ @@ -152,7 +152,7 @@ dsHsBind dflags b@(FunBind { fun_id = L _ fun, fun_matches = matches | xopt LangExt.Strict dflags , matchGroupArity matches == 0 -- no need to force lambdas = [id] - | isBangedBind b + | isBangedHsBind b = [id] | otherwise = [] @@ -603,7 +603,7 @@ We define an "unlifted bind" to be any bind that binds an unlifted id. Note that is *not* an unlifted bind. Unlifted binds are detected by HsUtils.isUnliftedHsBind. -Define a "banged bind" to have a top-level bang. Detected by HsPat.isBangedPatBind. +Define a "banged bind" to have a top-level bang. Detected by HsPat.isBangedHsBind. Define a "strict bind" to be either an unlifted bind or a banged bind. The restrictions are: diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs index edf2e1b..5caf1a0 100644 --- a/compiler/hsSyn/HsPat.hs +++ b/compiler/hsSyn/HsPat.hs @@ -29,7 +29,7 @@ module HsPat ( mkPrefixConPat, mkCharLitPat, mkNilPat, looksLazyPatBind, - isBangedLPat, isBangedPatBind, + isBangedLPat, hsPatNeedsParens, isIrrefutableHsPat, @@ -558,10 +558,6 @@ patterns are treated specially, of course. The 1.3 report defines what ``irrefutable'' and ``failure-free'' patterns are. -} -isBangedPatBind :: HsBind p -> Bool -isBangedPatBind (PatBind {pat_lhs = pat}) = isBangedLPat pat -isBangedPatBind _ = False - isBangedLPat :: LPat p -> Bool isBangedLPat (L _ (ParPat p)) = isBangedLPat p isBangedLPat (L _ (BangPat {})) = True diff --git a/compiler/hsSyn/HsUtils.hs b/compiler/hsSyn/HsUtils.hs index 5be757f..f409c2a 100644 --- a/compiler/hsSyn/HsUtils.hs +++ b/compiler/hsSyn/HsUtils.hs @@ -72,7 +72,7 @@ module HsUtils( noRebindableInfo, -- Collecting binders - isUnliftedHsBind, isBangedBind, + isUnliftedHsBind, isBangedHsBind, collectLocalBinders, collectHsValBinders, collectHsBindListBinders, collectHsIdBinders, @@ -844,14 +844,18 @@ isUnliftedHsBind bind where is_unlifted_id id = isUnliftedType (idType id) --- | Is a binding a strict variable bind (e.g. @!x = ...@)? -isBangedBind :: HsBind GhcTc -> Bool -isBangedBind b | isBangedPatBind b = True -isBangedBind (FunBind {fun_matches = matches}) +-- | Is a binding a strict variable or pattern bind (e.g. @!x = ...@)? +isBangedHsBind :: HsBind GhcTc -> Bool +isBangedHsBind (AbsBinds { abs_binds = binds }) + = anyBag (isBangedHsBind . unLoc) binds +isBangedHsBind (FunBind {fun_matches = matches}) | [L _ match] <- unLoc $ mg_alts matches , FunRhs{mc_strictness = SrcStrict} <- m_ctxt match = True -isBangedBind _ = False +isBangedHsBind (PatBind {pat_lhs = pat}) + = isBangedLPat pat +isBangedHsBind _ + = False collectLocalBinders :: HsLocalBindsLR idL idR -> [IdP idL] collectLocalBinders (HsValBinds binds) = collectHsIdBinders binds diff --git a/testsuite/tests/typecheck/should_compile/T13594.stderr b/testsuite/tests/typecheck/should_compile/T13594.stderr new file mode 100644 index 0000000..57810cc --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13594.stderr @@ -0,0 +1,3 @@ + +T13594.hs:8:1: error: + Top-level strict bindings aren't allowed: !x = (1, 2) diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 2ce4e91..c18c73b 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -556,7 +556,7 @@ test('T13474', normal, compile, ['']) test('T13524', normal, compile, ['']) test('T13509', normal, compile, ['']) test('T13526', normal, compile, ['']) -test('T13594', normal, compile, ['']) +test('T13594', normal, compile_fail, ['']) 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 Mon Jul 31 12:45:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Jul 2017 12:45:20 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: testsuite/junit: Flip type and message (f0dad2c) Message-ID: <20170731124520.03E5A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/f0dad2c554a014f36b18a10ed9fbd6d08dfd4cfa/ghc >--------------------------------------------------------------- commit f0dad2c554a014f36b18a10ed9fbd6d08dfd4cfa Author: Ben Gamari Date: Mon Jul 31 08:44:40 2017 -0400 testsuite/junit: Flip type and message type apparently can't contain < characters. >--------------------------------------------------------------- f0dad2c554a014f36b18a10ed9fbd6d08dfd4cfa testsuite/driver/junit.py | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/driver/junit.py b/testsuite/driver/junit.py index 01a5f47..f9689de 100644 --- a/testsuite/driver/junit.py +++ b/testsuite/driver/junit.py @@ -18,8 +18,8 @@ def junit(t): classname = testname, name = way) result = ET.SubElement(testcase, 'failure', - type = result, - message = reason) + type = reason, + message = result) for (directory, testname, reason, way) in t.framework_failures: testcase = ET.SubElement(testsuite, 'testcase', From git at git.haskell.org Mon Jul 31 17:37:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Jul 2017 17:37:38 +0000 (UTC) Subject: [commit: ghc] master: A bunch of typofixes (2ef973e) Message-ID: <20170731173738.CB6153A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2ef973e823ffb128f9f3b4b85b219e1627dceabf/ghc >--------------------------------------------------------------- commit 2ef973e823ffb128f9f3b4b85b219e1627dceabf Author: Gabor Greif Date: Mon Jul 31 17:34:43 2017 +0200 A bunch of typofixes >--------------------------------------------------------------- 2ef973e823ffb128f9f3b4b85b219e1627dceabf compiler/basicTypes/DataCon.hs | 2 +- compiler/basicTypes/PatSyn.hs | 2 +- compiler/nativeGen/RegAlloc/Graph/Coalesce.hs | 2 +- compiler/prelude/PrelRules.hs | 2 +- compiler/simplCore/CallArity.hs | 2 +- compiler/simplCore/SimplUtils.hs | 2 +- compiler/simplStg/StgCse.hs | 2 +- compiler/typecheck/TcHsType.hs | 2 +- compiler/typecheck/TcUnify.hs | 2 +- compiler/typecheck/TcValidity.hs | 2 +- compiler/types/TyCoRep.hs | 2 +- compiler/types/TyCon.hs | 2 +- docs/core-spec/CoreSyn.ott | 2 +- 13 files changed, 13 insertions(+), 13 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2ef973e823ffb128f9f3b4b85b219e1627dceabf From git at git.haskell.org Mon Jul 31 18:11:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Jul 2017 18:11:35 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: testsuite/junit: Properly escape strings (7a3622a) Message-ID: <20170731181135.CFD4A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7a3622aea1dfccc397ed6868d1625b5a283aa38c/ghc >--------------------------------------------------------------- commit 7a3622aea1dfccc397ed6868d1625b5a283aa38c Author: Ben Gamari Date: Mon Jul 31 11:36:49 2017 -0400 testsuite/junit: Properly escape strings >--------------------------------------------------------------- 7a3622aea1dfccc397ed6868d1625b5a283aa38c testsuite/driver/junit.py | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/testsuite/driver/junit.py b/testsuite/driver/junit.py index f9689de..237212d 100644 --- a/testsuite/driver/junit.py +++ b/testsuite/driver/junit.py @@ -1,5 +1,6 @@ from datetime import datetime import xml.etree.ElementTree as ET +from xml.sax.saxutils import escape def junit(t): testsuites = ET.Element('testsuites') @@ -18,21 +19,21 @@ def junit(t): classname = testname, name = way) result = ET.SubElement(testcase, 'failure', - type = reason, - message = result) + type = escape(reason), + message = escape(result)) for (directory, testname, reason, way) in t.framework_failures: testcase = ET.SubElement(testsuite, 'testcase', classname = testname, - name = way) + name = escape(way)) result = ET.SubElement(testcase, 'error', type = "framework failure", - message = reason) + message = escape(reason)) for (directory, testname, way) in t.expected_passes: testcase = ET.SubElement(testsuite, 'testcase', classname = testname, - name = way) + name = escape(way)) return ET.ElementTree(testsuites) From git at git.haskell.org Mon Jul 31 20:21:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Jul 2017 20:21:14 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: testsuite/junit: Properly escape strings (5d4fb3d) Message-ID: <20170731202114.1EE6C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/5d4fb3d9f7a8da40077b0ef0f8d9ce14edb8f3bb/ghc >--------------------------------------------------------------- commit 5d4fb3d9f7a8da40077b0ef0f8d9ce14edb8f3bb Author: Ben Gamari Date: Mon Jul 31 11:36:49 2017 -0400 testsuite/junit: Properly escape strings >--------------------------------------------------------------- 5d4fb3d9f7a8da40077b0ef0f8d9ce14edb8f3bb testsuite/driver/junit.py | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/testsuite/driver/junit.py b/testsuite/driver/junit.py index f9689de..4015c19 100644 --- a/testsuite/driver/junit.py +++ b/testsuite/driver/junit.py @@ -1,5 +1,6 @@ from datetime import datetime import xml.etree.ElementTree as ET +from xml.sax.saxutils import escape def junit(t): testsuites = ET.Element('testsuites') @@ -18,21 +19,21 @@ def junit(t): classname = testname, name = way) result = ET.SubElement(testcase, 'failure', - type = reason, - message = result) + type = 'unexpected failure', + message = escape(reason)) for (directory, testname, reason, way) in t.framework_failures: testcase = ET.SubElement(testsuite, 'testcase', classname = testname, - name = way) + name = escape(way)) result = ET.SubElement(testcase, 'error', type = "framework failure", - message = reason) + message = escape(reason)) for (directory, testname, way) in t.expected_passes: testcase = ET.SubElement(testsuite, 'testcase', classname = testname, - name = way) + name = escape(way)) return ET.ElementTree(testsuites)