From git at git.haskell.org Thu Jun 1 21:34:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Jun 2017 21:34:32 +0000 (UTC) Subject: [commit: ghc] master: aclocal.m4: add support for versioned darwin triplets (d39a340) Message-ID: <20170601213432.EEF043A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d39a3409acd3c40fb018ec1c114f15d3ecef6ef9/ghc >--------------------------------------------------------------- commit d39a3409acd3c40fb018ec1c114f15d3ecef6ef9 Author: Sergei Trofimovich Date: Thu Jun 1 22:30:05 2017 +0100 aclocal.m4: add support for versioned darwin triplets The change adds support for 'darwin*' OS: $ ./configure --target=aarch64-apple-darwin14 Reported-by: jp_rider Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- d39a3409acd3c40fb018ec1c114f15d3ecef6ef9 aclocal.m4 | 3 +++ 1 file changed, 3 insertions(+) diff --git a/aclocal.m4 b/aclocal.m4 index 7ad9c36..437974a 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -1906,6 +1906,9 @@ AC_DEFUN([GHC_CONVERT_OS],[ aix*) # e.g. powerpc-ibm-aix7.1.3.0 $3="aix" ;; + darwin*) # e.g. aarch64-apple-darwin14 + $3="darwin" + ;; freebsd*) # like i686-gentoo-freebsd7 # i686-gentoo-freebsd8 # i686-gentoo-freebsd8.2 From git at git.haskell.org Fri Jun 2 09:09:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Jun 2017 09:09:10 +0000 (UTC) Subject: [commit: ghc] master: A few typos [ci skip] (750a25f) Message-ID: <20170602090910.050613A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/750a25f47b626e6495cc6f951eca071429744767/ghc >--------------------------------------------------------------- commit 750a25f47b626e6495cc6f951eca071429744767 Author: Gabor Greif Date: Fri Jun 2 11:02:13 2017 +0200 A few typos [ci skip] >--------------------------------------------------------------- 750a25f47b626e6495cc6f951eca071429744767 compiler/prelude/TysWiredIn.hs | 2 +- compiler/rename/RnTypes.hs | 2 +- compiler/typecheck/TcRnTypes.hs | 2 +- testsuite/tests/programs/andy_cherry/GenUtils.hs | 4 ++-- 4 files changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index b683564..71ff0e1 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -1080,7 +1080,7 @@ runtimeRepTy = mkTyConTy runtimeRepTyCon liftedTypeKindTyCon, starKindTyCon, unicodeStarKindTyCon :: TyCon --- Type syononyms; see Note [TYPE and RuntimeRep] in TysPrim +-- Type synonyms; see Note [TYPE and RuntimeRep] in TysPrim -- type Type = tYPE 'LiftedRep -- type * = tYPE 'LiftedRep -- type * = tYPE 'LiftedRep -- Unicode variant diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs index 492862b..7571684 100644 --- a/compiler/rename/RnTypes.hs +++ b/compiler/rename/RnTypes.hs @@ -721,7 +721,7 @@ checkWildCard _ Nothing = return () checkAnonWildCard :: RnTyKiEnv -> HsWildCardInfo RdrName -> RnM () --- Report an error if an anonymoous wildcard is illegal here +-- Report an error if an anonymous wildcard is illegal here checkAnonWildCard env wc = checkWildCard env mb_bad where diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index e018d5d..651e735 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -879,7 +879,7 @@ type TcIdSet = IdSet type TcIdBinderStack = [TcIdBinder] -- This is a stack of locally-bound ids, innermost on top - -- Used ony in error reporting (relevantBindings in TcError) + -- Used only in error reporting (relevantBindings in TcError) -- We can't use the tcl_env type environment, because it doesn't -- keep track of the nesting order diff --git a/testsuite/tests/programs/andy_cherry/GenUtils.hs b/testsuite/tests/programs/andy_cherry/GenUtils.hs index 8ff6757..2a0a9606f 100644 --- a/testsuite/tests/programs/andy_cherry/GenUtils.hs +++ b/testsuite/tests/programs/andy_cherry/GenUtils.hs @@ -189,8 +189,8 @@ mapAccumL f s (b:bs) = (c:cs,s'') --- Now some utilties involving arrays. --- Here is a version of @elem@ that uses partual application +-- Now some utilities involving arrays. +-- Here is a version of @elem@ that uses partial application -- to optimise lookup. arrElem :: (Ix a) => [a] -> a -> Bool From git at git.haskell.org Fri Jun 2 16:28:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Jun 2017 16:28:06 +0000 (UTC) Subject: [commit: ghc] master: Better import library support for Windows (93489cd) Message-ID: <20170602162806.908453A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/93489cd3b4c1b0d17506a12a9b964c0082ddb7a8/ghc >--------------------------------------------------------------- commit 93489cd3b4c1b0d17506a12a9b964c0082ddb7a8 Author: Tamar Christina Date: Fri Jun 2 11:47:57 2017 -0400 Better import library support for Windows The import library support added for 7.10.3 was only a partial one. This support was predicated on using file extensions to determine whether or not a library was an import library. It also couldn't handle libraries with multiple dll pointers. This is a rewrite of that patch and fully integrating it into the normal archive parsing and loading routines. This solves a host of issues, among others allowing us to finally use `-lgcc_s`. This also fixes a problem with our previous implementation, where we just loaded the DLL and moved on. Doing this had the potential of using the wrong symbol at resolve time. Say a DLL already loaded (A.dll) has symbol a exported (dependency of another dll perhaps). We find an import library `B.lib` explicitly defining an export of `a`. we load `B.dll` but this gets put after `A.dll`, at resolve time we would use the value from `A` instead of `B` which is what we wanted. Test Plan: ./valide and make test TEST=13606 Reviewers: austin, bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, RyanGlScott, thomie, #ghc_windows_task_force GHC Trac Issues: #13606, #12499, #12498 Differential Revision: https://phabricator.haskell.org/D3513 >--------------------------------------------------------------- 93489cd3b4c1b0d17506a12a9b964c0082ddb7a8 docs/users_guide/8.4.1-notes.rst | 4 + rts/Linker.c | 5 +- rts/LinkerInternals.h | 14 +- rts/RtsSymbolInfo.c | 113 ++++++--- rts/RtsSymbolInfo.h | 23 +- rts/linker/LoadArchive.c | 26 +-- rts/linker/PEi386.c | 310 ++++++++++++++++++------- rts/linker/PEi386.h | 5 +- testsuite/tests/ghci/linking/dyn/Makefile | 4 + testsuite/tests/ghci/linking/dyn/T13606.hs | 128 ++++++++++ testsuite/tests/ghci/linking/dyn/T13606.stdout | 2 + testsuite/tests/ghci/linking/dyn/Triangle.fx | 10 + testsuite/tests/ghci/linking/dyn/all.T | 4 + 13 files changed, 498 insertions(+), 150 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 93489cd3b4c1b0d17506a12a9b964c0082ddb7a8 From git at git.haskell.org Fri Jun 2 16:28:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Jun 2017 16:28:09 +0000 (UTC) Subject: [commit: ghc] master: Add a flag reference entry for -XTypeInType (d0fb0df) Message-ID: <20170602162809.4BBC03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d0fb0df349d0e51b2b3f7980a8b1eca80051d67f/ghc >--------------------------------------------------------------- commit d0fb0df349d0e51b2b3f7980a8b1eca80051d67f Author: Ryan Scott Date: Fri Jun 2 11:48:44 2017 -0400 Add a flag reference entry for -XTypeInType Test Plan: Read it Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13762 Differential Revision: https://phabricator.haskell.org/D3614 >--------------------------------------------------------------- d0fb0df349d0e51b2b3f7980a8b1eca80051d67f utils/mkUserGuidePart/Options/Language.hs | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/utils/mkUserGuidePart/Options/Language.hs b/utils/mkUserGuidePart/Options/Language.hs index f0aeb49..e584d2f 100644 --- a/utils/mkUserGuidePart/Options/Language.hs +++ b/utils/mkUserGuidePart/Options/Language.hs @@ -702,6 +702,17 @@ languageOptions = , flagReverse = "-XNoTypeFamilies" , flagSince = "6.8.1" } + , flag { flagName = "-XTypeInType" + , flagDescription = + "Allow :ref:`kinds to be used as types `, " ++ + "including explicit kind variable quantification, higher-rank "++ + "kinds, kind synonyms, and kind families. "++ + "Implies :ghc-flag:`-XDataKinds`, :ghc-flag:`-XKindSignatures`, " ++ + "and :ghc-flag:`-XPolyKinds`." + , flagType = DynamicFlag + , flagReverse = "-XNoTypeInType" + , flagSince = "8.0.1" + } , flag { flagName = "-XTypeOperators" , flagDescription = "Enable :ref:`type operators `. "++ From git at git.haskell.org Fri Jun 2 16:28:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Jun 2017 16:28:12 +0000 (UTC) Subject: [commit: ghc] master: [iserv] move forkIO (35c7ea8) Message-ID: <20170602162812.0E1E93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/35c7ea8b01a849aceca5c017989043d4cb6fe8a6/ghc >--------------------------------------------------------------- commit 35c7ea8b01a849aceca5c017989043d4cb6fe8a6 Author: Moritz Angermann Date: Sat May 27 10:26:44 2017 -0400 [iserv] move forkIO This moves the forkIO into the `startSlave` function from the `startSlave'` function, such that this allows consumers to call `forkSlave'` if they want the blocking behaviour. Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: Ericson2314, ryantrinkle, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3601 >--------------------------------------------------------------- 35c7ea8b01a849aceca5c017989043d4cb6fe8a6 iserv/src/Remote/Slave.hs | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/iserv/src/Remote/Slave.hs b/iserv/src/Remote/Slave.hs index 11cc68a..c5b652d 100644 --- a/iserv/src/Remote/Slave.hs +++ b/iserv/src/Remote/Slave.hs @@ -46,14 +46,18 @@ startSlave verbose port s = do putStr "DocRoot: " base_path <- peekCString s putStrLn base_path - startSlave' verbose base_path (toEnum port) + _ <- forkIO $ startSlave' verbose base_path (toEnum port) + return () +-- | @startSlave'@ provdes a blocking haskell interface, that +-- the hosting application on the target can use to start the +-- slave process. startSlave' :: Bool -> String -> PortNumber -> IO () startSlave' verbose base_path port = do sock <- openSocket port - _ <- forkIO $ forever $ do + forever $ do when verbose $ putStrLn "Opening socket" pipe <- acceptSocket sock >>= socketToPipe putStrLn $ "Listening on port " ++ show port @@ -62,8 +66,6 @@ startSlave' verbose base_path port = do when verbose $ putStrLn "serv ended" return () - return () - -- | The iserv library may need access to files, specifically -- archives and object files to be linked. If ghc and the slave -- are on the same host, this is trivial, as the underlying From git at git.haskell.org Fri Jun 2 16:28:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Jun 2017 16:28:14 +0000 (UTC) Subject: [commit: ghc] master: Make GHCi work when RebindableSyntax is enabled (2abe54e) Message-ID: <20170602162814.C944E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2abe54e16cbd14cab27abdc7967e907753354d54/ghc >--------------------------------------------------------------- commit 2abe54e16cbd14cab27abdc7967e907753354d54 Author: Ryan Scott Date: Fri Jun 2 11:49:47 2017 -0400 Make GHCi work when RebindableSyntax is enabled Previously, we were running some blocks of code at the start of every GHCi sessions which use do-notation, something which doesn't work well if you start GHCi with the `-XRebindableSyntax` flag on. This tweaks the code to avoid the use of do-notation so that `-XRebindableSyntax` won't reject it. Test Plan: make test TEST=T13385 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13385 Differential Revision: https://phabricator.haskell.org/D3621 >--------------------------------------------------------------- 2abe54e16cbd14cab27abdc7967e907753354d54 ghc/GHCi/UI/Monad.hs | 12 +++++++----- .../tests/ghci/scripts/T13385.script | 0 testsuite/tests/ghci/scripts/all.T | 1 + 3 files changed, 8 insertions(+), 5 deletions(-) diff --git a/ghc/GHCi/UI/Monad.hs b/ghc/GHCi/UI/Monad.hs index 244595b..b57a5a0 100644 --- a/ghc/GHCi/UI/Monad.hs +++ b/ghc/GHCi/UI/Monad.hs @@ -420,13 +420,15 @@ foreign import ccall "revertCAFs" rts_revertCAFs :: IO () -- | Compile "hFlush stdout; hFlush stderr" once, so we can use it repeatedly initInterpBuffering :: Ghc (ForeignHValue, ForeignHValue) initInterpBuffering = do + -- We take great care not to use do-notation in the expressions below, as + -- they are fragile in the presence of RebindableSyntax (Trac #13385). nobuf <- GHC.compileExprRemote $ - "do { System.IO.hSetBuffering System.IO.stdin System.IO.NoBuffering; " ++ - " System.IO.hSetBuffering System.IO.stdout System.IO.NoBuffering; " ++ - " System.IO.hSetBuffering System.IO.stderr System.IO.NoBuffering }" + " System.IO.hSetBuffering System.IO.stdin System.IO.NoBuffering" ++ + "`GHC.Base.thenIO` System.IO.hSetBuffering System.IO.stdout System.IO.NoBuffering" ++ + "`GHC.Base.thenIO` System.IO.hSetBuffering System.IO.stderr System.IO.NoBuffering" flush <- GHC.compileExprRemote $ - "do { System.IO.hFlush System.IO.stdout; " ++ - " System.IO.hFlush System.IO.stderr }" + " System.IO.hFlush System.IO.stdout" ++ + "`GHC.Base.thenIO` System.IO.hFlush System.IO.stderr" return (nobuf, flush) -- | Invoke "hFlush stdout; hFlush stderr" in the interpreter diff --git a/libraries/ghc-compact/tests/compact_serialize.stderr b/testsuite/tests/ghci/scripts/T13385.script similarity index 100% copy from libraries/ghc-compact/tests/compact_serialize.stderr copy to testsuite/tests/ghci/scripts/T13385.script diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 8ef45fe..8c3a2f5 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -251,6 +251,7 @@ test('T12550', normal, ghci_script, ['T12550.script']) test('StaticPtr', normal, ghci_script, ['StaticPtr.script']) test('T13202', normal, ghci_script, ['T13202.script']) test('T13202a', normal, ghci_script, ['T13202a.script']) +test('T13385', [extra_hc_opts("-XRebindableSyntax")], ghci_script, ['T13385.script']) test('T13420', normal, ghci_script, ['T13420.script']) test('T13466', normal, ghci_script, ['T13466.script']) test('GhciCurDir', normal, ghci_script, ['GhciCurDir.script']) From git at git.haskell.org Fri Jun 2 16:28:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Jun 2017 16:28:17 +0000 (UTC) Subject: [commit: ghc] master: aclocal: Fix regression in linker detection (5164cce) Message-ID: <20170602162817.8584B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5164cce20bc6f09f55cf5c4d1797b72b7e85b176/ghc >--------------------------------------------------------------- commit 5164cce20bc6f09f55cf5c4d1797b72b7e85b176 Author: Ben Gamari Date: Fri Jun 2 09:36:01 2017 -0400 aclocal: Fix regression in linker detection 5ddb307edf15c4d86e5c35c4063ec967424e19f2 regressed autoconf's ability to find the linker due to a silly variable interpolation issue, causing segmentation faults on AArch64. >--------------------------------------------------------------- 5164cce20bc6f09f55cf5c4d1797b72b7e85b176 aclocal.m4 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/aclocal.m4 b/aclocal.m4 index 437974a..adc70bc 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -581,7 +581,7 @@ AC_DEFUN([FP_SET_CFLAGS_C99], # $5 is the name of the CPP flags variable AC_DEFUN([FPTOOLS_SET_C_LD_FLAGS], [ - FIND_LD([$1],[UseLd]) + FIND_LD([$$1],[UseLd]) AC_MSG_CHECKING([Setting up $2, $3, $4 and $5]) case $$1 in i386-*) From git at git.haskell.org Fri Jun 2 16:28:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Jun 2017 16:28:23 +0000 (UTC) Subject: [commit: ghc] master: GHC.Stats cleanup (811a298) Message-ID: <20170602162823.05AD73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/811a2986475d88f73bb22b4600970039e1b582d6/ghc >--------------------------------------------------------------- commit 811a2986475d88f73bb22b4600970039e1b582d6 Author: Ryan Scott Date: Fri Jun 2 11:52:41 2017 -0400 GHC.Stats cleanup This does two things: * The `RtsTime` type wasn't exported, but it is used as the type of several record fields. Let's export it and give it some documentation. * Neither `RTSStats` nor `GCDetails` have `Read` or `Show` instances, but `GCStats` does! Let's fix this discrepancy. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: goldfire, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3625 >--------------------------------------------------------------- 811a2986475d88f73bb22b4600970039e1b582d6 libraries/base/GHC/Stats.hsc | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/libraries/base/GHC/Stats.hsc b/libraries/base/GHC/Stats.hsc index d5d48f5..c4e2e80 100644 --- a/libraries/base/GHC/Stats.hsc +++ b/libraries/base/GHC/Stats.hsc @@ -15,7 +15,7 @@ module GHC.Stats ( -- * Runtime statistics - RTSStats(..), GCDetails(..) + RTSStats(..), GCDetails(..), RtsTime , getRTSStats , getRTSStatsEnabled @@ -104,7 +104,7 @@ data RTSStats = RTSStats { -- | Details about the most recent GC , gc :: GCDetails - } + } deriving (Read, Show) -- -- | Statistics about a single GC. This is a mirror of the C @struct @@ -138,9 +138,9 @@ data GCDetails = GCDetails { , gcdetails_cpu_ns :: RtsTime -- | The time elapsed during GC itself , gcdetails_elapsed_ns :: RtsTime - } - + } deriving (Read, Show) +-- | Time values from the RTS, using a fixed resolution of nanoseconds. type RtsTime = Int64 -- @since 4.9.0.0 From git at git.haskell.org Fri Jun 2 16:28:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Jun 2017 16:28:20 +0000 (UTC) Subject: [commit: ghc] master: Remove references to static flags in flag reference (bf775e9) Message-ID: <20170602162820.411913A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bf775e9d6895c07f629409ee18503f40730cb5a0/ghc >--------------------------------------------------------------- commit bf775e9d6895c07f629409ee18503f40730cb5a0 Author: Ryan Scott Date: Fri Jun 2 11:48:57 2017 -0400 Remove references to static flags in flag reference A follow-up to #8440 (Ditch static flags). There are still some lingering references to static flags in the flag reference, so let's modify those references accordingly. Test Plan: Build the documentation Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3615 >--------------------------------------------------------------- bf775e9d6895c07f629409ee18503f40730cb5a0 utils/mkUserGuidePart/Main.hs | 3 +-- utils/mkUserGuidePart/Options/CompilerDebugging.hs | 4 ++-- utils/mkUserGuidePart/Options/Optimizations.hs | 4 ++-- utils/mkUserGuidePart/Types.hs | 4 +--- 4 files changed, 6 insertions(+), 9 deletions(-) diff --git a/utils/mkUserGuidePart/Main.hs b/utils/mkUserGuidePart/Main.hs index 344c808..d517048 100644 --- a/utils/mkUserGuidePart/Main.hs +++ b/utils/mkUserGuidePart/Main.hs @@ -49,7 +49,7 @@ whatGlasgowExtsDoes = unlines flagsTable :: [Flag] -> ReST flagsTable theFlags = table [50, 100, 30, 55] - ["Flag", "Description", "Static/Dynamic", "Reverse"] + ["Flag", "Description", "Type", "Reverse"] (map flagRow theFlags) where flagRow flag = @@ -60,7 +60,6 @@ flagsTable theFlags = ] where type_ = case flagType flag of - StaticFlag -> "static" DynamicFlag -> "dynamic" DynamicSettableFlag -> "dynamic/``:set``" ModeFlag -> "mode" diff --git a/utils/mkUserGuidePart/Options/CompilerDebugging.hs b/utils/mkUserGuidePart/Options/CompilerDebugging.hs index c886156..9704020 100644 --- a/utils/mkUserGuidePart/Options/CompilerDebugging.hs +++ b/utils/mkUserGuidePart/Options/CompilerDebugging.hs @@ -175,11 +175,11 @@ compilerDebuggingOptions = } , flag { flagName = "-dno-debug-output" , flagDescription = "Suppress unsolicited debugging output" - , flagType = StaticFlag + , flagType = DynamicFlag } , flag { flagName = "-dppr-debug" , flagDescription = "Turn on debug printing (more verbose)" - , flagType = StaticFlag + , flagType = DynamicFlag } , flag { flagName = "-dppr-user-length" , flagDescription = diff --git a/utils/mkUserGuidePart/Options/Optimizations.hs b/utils/mkUserGuidePart/Options/Optimizations.hs index 992390b..afefc6e 100644 --- a/utils/mkUserGuidePart/Options/Optimizations.hs +++ b/utils/mkUserGuidePart/Options/Optimizations.hs @@ -209,7 +209,7 @@ optimizationsOptions = } , flag { flagName = "-fno-opt-coercion" , flagDescription = "Turn off the coercion optimiser" - , flagType = StaticFlag + , flagType = DynamicFlag } , flag { flagName = "-fno-pre-inlining" , flagDescription = "Turn off pre-inlining" @@ -220,7 +220,7 @@ optimizationsOptions = "Turn off the \"state hack\" whereby any lambda with a real-world "++ "state token as argument is considered to be single-entry. Hence "++ "OK to inline things inside it." - , flagType = StaticFlag + , flagType = DynamicFlag } , flag { flagName = "-fomit-interface-pragmas" , flagDescription = diff --git a/utils/mkUserGuidePart/Types.hs b/utils/mkUserGuidePart/Types.hs index 33474da..340672e 100644 --- a/utils/mkUserGuidePart/Types.hs +++ b/utils/mkUserGuidePart/Types.hs @@ -1,8 +1,6 @@ module Types where -data FlagType = StaticFlag - -- ^ Static flag - | DynamicFlag +data FlagType = DynamicFlag -- ^ Dynamic flag | DynamicSettableFlag -- ^ Dynamic flag on which @:set@ can be used in GHCi From git at git.haskell.org Fri Jun 2 18:02:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Jun 2017 18:02:23 +0000 (UTC) Subject: [commit: ghc] master: ghc.mk: Ensure that ghc-pkg path is quoted (ff363bd) Message-ID: <20170602180223.915FD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ff363bd74c8b2505b92b39d5fedcf95b8ab7365a/ghc >--------------------------------------------------------------- commit ff363bd74c8b2505b92b39d5fedcf95b8ab7365a 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 >--------------------------------------------------------------- ff363bd74c8b2505b92b39d5fedcf95b8ab7365a ghc.mk | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.mk b/ghc.mk index 2272569..3fafcf0 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1039,7 +1039,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 Fri Jun 2 18:02:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Jun 2017 18:02:20 +0000 (UTC) Subject: [commit: ghc] master: Use lengthIs and friends in more places (a786b13) Message-ID: <20170602180220.C402C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a786b136f48dfcf907dad55bcdbc4fcd247f2794/ghc >--------------------------------------------------------------- commit a786b136f48dfcf907dad55bcdbc4fcd247f2794 Author: Ryan Scott Date: Fri Jun 2 13:12:11 2017 -0400 Use lengthIs and friends in more places While investigating #12545, I discovered several places in the code that performed length-checks like so: ``` length ts == 4 ``` This is not ideal, since the length of `ts` could be much longer than 4, and we'd be doing way more work than necessary! There are already a slew of helper functions in `Util` such as `lengthIs` that are designed to do this efficiently, so I found every place where they ought to be used and did just that. I also defined a couple more utility functions for list length that were common patterns (e.g., `ltLength`). Test Plan: ./validate Reviewers: austin, hvr, goldfire, bgamari, simonmar Reviewed By: bgamari, simonmar Subscribers: goldfire, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3622 >--------------------------------------------------------------- a786b136f48dfcf907dad55bcdbc4fcd247f2794 compiler/basicTypes/DataCon.hs | 4 +-- compiler/basicTypes/Demand.hs | 8 +++--- compiler/basicTypes/MkId.hs | 2 +- compiler/basicTypes/PatSyn.hs | 4 +-- compiler/cmm/CmmBuildInfoTables.hs | 2 +- compiler/cmm/CmmContFlowOpt.hs | 3 ++- compiler/codeGen/StgCmmClosure.hs | 2 +- compiler/codeGen/StgCmmExpr.hs | 2 +- compiler/codeGen/StgCmmLayout.hs | 2 +- compiler/codeGen/StgCmmPrim.hs | 4 +-- compiler/codeGen/StgCmmTicky.hs | 5 ++-- compiler/coreSyn/CoreLint.hs | 12 ++++----- compiler/coreSyn/CoreUnfold.hs | 4 +-- compiler/coreSyn/CoreUtils.hs | 8 +++--- compiler/coreSyn/TrieMap.hs | 3 ++- compiler/deSugar/Check.hs | 12 +++------ compiler/deSugar/Coverage.hs | 2 +- compiler/deSugar/DsExpr.hs | 4 +-- compiler/deSugar/MatchCon.hs | 2 +- compiler/ghci/ByteCodeGen.hs | 4 +-- compiler/ghci/DebuggerUtils.hs | 4 +-- compiler/hsSyn/Convert.hs | 6 ++--- compiler/main/InteractiveEval.hs | 3 ++- compiler/nativeGen/Dwarf/Types.hs | 3 ++- compiler/prelude/PrelInfo.hs | 2 +- compiler/rename/RnPat.hs | 2 +- compiler/simplCore/CallArity.hs | 7 ++--- compiler/simplCore/FloatIn.hs | 2 +- compiler/simplCore/OccurAnal.hs | 4 +-- compiler/simplStg/RepType.hs | 2 +- compiler/simplStg/UnariseStg.hs | 2 +- compiler/specialise/SpecConstr.hs | 2 +- compiler/stgSyn/StgLint.hs | 4 +-- compiler/typecheck/FamInst.hs | 2 +- compiler/typecheck/FunDeps.hs | 4 +-- compiler/typecheck/TcCanonical.hs | 2 +- compiler/typecheck/TcDeriv.hs | 6 ++--- compiler/typecheck/TcDerivInfer.hs | 8 +++--- compiler/typecheck/TcErrors.hs | 6 ++--- compiler/typecheck/TcFlatten.hs | 2 +- compiler/typecheck/TcGenDeriv.hs | 4 +-- compiler/typecheck/TcGenGenerics.hs | 6 ++--- compiler/typecheck/TcPat.hs | 2 +- compiler/typecheck/TcSplice.hs | 4 +-- compiler/typecheck/TcTyClsDecls.hs | 4 +-- compiler/typecheck/TcUnify.hs | 2 +- compiler/typecheck/TcValidity.hs | 12 ++++----- compiler/types/Class.hs | 2 +- compiler/types/Coercion.hs | 6 ++--- compiler/types/OptCoercion.hs | 6 ++--- compiler/types/TyCoRep.hs | 20 +++++++-------- compiler/types/TyCon.hs | 10 ++++---- compiler/types/Type.hs | 12 ++++----- compiler/utils/ListSetOps.hs | 2 +- compiler/utils/Util.hs | 38 ++++++++++++++++++++++++++-- compiler/vectorise/Vectorise/Type/Env.hs | 2 +- compiler/vectorise/Vectorise/Utils/PADict.hs | 3 ++- ghc/GHCi/UI/Monad.hs | 5 ++-- 58 files changed, 170 insertions(+), 132 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 a786b136f48dfcf907dad55bcdbc4fcd247f2794 From git at git.haskell.org Sat Jun 3 19:12:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Jun 2017 19:12:58 +0000 (UTC) Subject: [commit: ghc] wip/new-tree-one-param-2: Udate hsSyn AST to use Trees that Grow (ebc896e) Message-ID: <20170603191258.C59243A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-tree-one-param-2 Link : http://ghc.haskell.org/trac/ghc/changeset/ebc896ed944f9a00ce1352b2b22ed2678f788398/ghc >--------------------------------------------------------------- commit ebc896ed944f9a00ce1352b2b22ed2678f788398 Author: Alan Zimmerman Date: Fri May 19 14:56:09 2017 +0200 Udate hsSyn AST to use Trees that Grow Summary: See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow This commit prepares the ground for a full extensible AST, by replacing the type parameter for the hsSyn data types with a set of indices into type families, data GhcPs -- ^ Index for GHC parser output data GhcRn -- ^ Index for GHC renamer output data GhcTc -- ^ Index for GHC typechecker output These are now used instead of `RdrName`, `Name` and `Id`/`TcId`/`Var` Where the original name type is required in a polymorphic context, this is accessible via the IdP type family, defined as type family IdP p type instance IdP GhcPs = RdrName type instance IdP GhcRn = Name type instance IdP GhcTc = Id These types are declared in the new 'hsSyn/HsExtension.hs' module. To gain a better understanding of the extension mechanism, it has been applied to `HsLit` only, also replacing the `SourceText` fields in them with extension types. To preserve extension generality, a type class is introduced to capture the `SourceText` interface, which must be honoured by all of the extension points which originally had a `SourceText`. The class is defined as class HasSourceText a where -- Provide setters to mimic existing constructors noSourceText :: a sourceText :: String -> a setSourceText :: SourceText -> a getSourceText :: a -> SourceText And the constraint is captured in `SourceTextX`, which is a constraint type listing all the extension points that make use of the class. Updating Haddock submodule to match. Test Plan: ./validate Reviewers: simonpj, shayan-najd, goldfire, austin, bgamari Subscribers: rwbarton, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D3609 >--------------------------------------------------------------- ebc896ed944f9a00ce1352b2b22ed2678f788398 compiler/backpack/BkpSyn.hs | 3 +- compiler/backpack/DriverBkp.hs | 4 +- compiler/deSugar/Check.hs | 66 +-- compiler/deSugar/Coverage.hs | 122 ++--- compiler/deSugar/Desugar.hs | 7 +- compiler/deSugar/DsArrows.hs | 71 +-- compiler/deSugar/DsBinds.hs | 16 +- compiler/deSugar/DsExpr.hs | 41 +- compiler/deSugar/DsExpr.hs-boot | 16 +- compiler/deSugar/DsForeign.hs | 10 +- compiler/deSugar/DsGRHSs.hs | 18 +- compiler/deSugar/DsListComp.hs | 59 +-- compiler/deSugar/DsMeta.hs | 231 ++++----- compiler/deSugar/DsMonad.hs | 2 +- compiler/deSugar/DsUtils.hs | 29 +- compiler/deSugar/Match.hs | 43 +- compiler/deSugar/Match.hs-boot | 9 +- compiler/deSugar/MatchCon.hs | 8 +- compiler/deSugar/MatchLit.hs | 40 +- compiler/deSugar/PmExpr.hs | 12 +- compiler/ghc.cabal.in | 1 + compiler/ghc.mk | 1 + compiler/hsSyn/Convert.hs | 149 +++--- compiler/hsSyn/HsBinds.hs | 121 ++--- compiler/hsSyn/HsDecls.hs | 531 +++++++++++---------- compiler/hsSyn/HsDumpAst.hs | 28 +- compiler/hsSyn/HsExpr.hs | 461 +++++++++--------- compiler/hsSyn/HsExpr.hs-boot | 40 +- compiler/hsSyn/HsExtension.hs | 267 +++++++++++ compiler/hsSyn/HsImpExp.hs | 37 +- compiler/hsSyn/HsLit.hs | 132 +++-- compiler/hsSyn/HsPat.hs | 183 +++---- compiler/hsSyn/HsPat.hs-boot | 6 +- compiler/hsSyn/HsSyn.hs | 7 +- compiler/hsSyn/HsTypes.hs | 392 +++++++-------- compiler/hsSyn/HsUtils.hs | 297 ++++++------ compiler/hsSyn/PlaceHolder.hs | 50 -- compiler/main/GHC.hs | 8 +- compiler/main/HeaderInfo.hs | 7 +- compiler/main/Hooks.hs | 28 +- compiler/main/HscMain.hs | 16 +- compiler/main/HscStats.hs | 3 +- compiler/main/HscTypes.hs | 34 +- compiler/main/InteractiveEval.hs | 10 +- compiler/parser/Parser.y | 373 ++++++++------- compiler/parser/RdrHsSyn.hs | 245 +++++----- compiler/rename/RnBinds.hs | 150 +++--- compiler/rename/RnEnv.hs | 29 +- compiler/rename/RnExpr.hs | 226 ++++----- compiler/rename/RnExpr.hs-boot | 22 +- compiler/rename/RnFixity.hs | 2 +- compiler/rename/RnNames.hs | 87 ++-- compiler/rename/RnPat.hs | 64 +-- compiler/rename/RnSource.hs | 187 ++++---- compiler/rename/RnSplice.hs | 63 +-- compiler/rename/RnSplice.hs-boot | 12 +- compiler/rename/RnTypes.hs | 211 ++++---- compiler/rename/RnUtils.hs | 2 +- compiler/typecheck/Inst.hs | 29 +- compiler/typecheck/TcAnnotations.hs | 17 +- compiler/typecheck/TcArrows.hs | 19 +- compiler/typecheck/TcBackpack.hs | 1 + compiler/typecheck/TcBinds.hs | 96 ++-- compiler/typecheck/TcClassDcl.hs | 41 +- compiler/typecheck/TcDefaults.hs | 8 +- compiler/typecheck/TcDeriv.hs | 39 +- compiler/typecheck/TcDerivUtils.hs | 8 +- compiler/typecheck/TcEnv.hs | 18 +- compiler/typecheck/TcEnv.hs-boot | 1 + compiler/typecheck/TcExpr.hs | 146 +++--- compiler/typecheck/TcExpr.hs-boot | 31 +- compiler/typecheck/TcForeign.hs | 23 +- compiler/typecheck/TcGenDeriv.hs | 151 +++--- compiler/typecheck/TcGenFunctor.hs | 99 ++-- compiler/typecheck/TcGenGenerics.hs | 32 +- compiler/typecheck/TcHsSyn.hs | 137 +++--- compiler/typecheck/TcHsType.hs | 93 ++-- compiler/typecheck/TcInstDcls.hs | 72 +-- compiler/typecheck/TcInstDcls.hs-boot | 5 +- compiler/typecheck/TcMatches.hs | 106 ++-- compiler/typecheck/TcMatches.hs-boot | 11 +- compiler/typecheck/TcPat.hs | 53 +- compiler/typecheck/TcPatSyn.hs | 86 ++-- compiler/typecheck/TcPatSyn.hs-boot | 13 +- compiler/typecheck/TcRnDriver.hs | 63 +-- compiler/typecheck/TcRnExports.hs | 41 +- compiler/typecheck/TcRnTypes.hs | 73 +-- compiler/typecheck/TcRules.hs | 10 +- compiler/typecheck/TcSigs.hs | 34 +- compiler/typecheck/TcSplice.hs | 53 +- compiler/typecheck/TcSplice.hs-boot | 36 +- compiler/typecheck/TcTyClsDecls.hs | 112 ++--- compiler/typecheck/TcTyDecls.hs | 11 +- compiler/typecheck/TcTypeable.hs | 55 +-- compiler/typecheck/TcUnify.hs | 11 +- compiler/typecheck/TcUnify.hs-boot | 14 +- compiler/typecheck/TcValidity.hs | 2 +- ghc/GHCi/UI.hs | 6 +- ghc/GHCi/UI/Info.hs | 6 +- ghc/GHCi/UI/Monad.hs | 7 +- .../tests/ghc-api/annotations-literals/parsed.hs | 6 +- testsuite/tests/ghc-api/annotations/parseTree.hs | 2 +- .../tests/ghc-api/annotations/stringSource.hs | 6 +- testsuite/tests/ghc-api/annotations/t11430.hs | 4 +- testsuite/tests/quasiquotation/T7918.hs | 6 +- utils/ghctags/Main.hs | 5 +- utils/haddock | 2 +- 107 files changed, 3861 insertions(+), 3328 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ebc896ed944f9a00ce1352b2b22ed2678f788398 From git at git.haskell.org Sat Jun 3 19:13:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Jun 2017 19:13:01 +0000 (UTC) Subject: [commit: ghc] wip/new-tree-one-param-2's head updated: Udate hsSyn AST to use Trees that Grow (ebc896e) Message-ID: <20170603191301.35EB93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/new-tree-one-param-2' now includes: 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 ebc896e Udate hsSyn AST to use Trees that Grow From git at git.haskell.org Sat Jun 3 21:02:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Jun 2017 21:02:11 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: More debugging (d7fbc6a) Message-ID: <20170603210211.496A63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d7fbc6a33bd259b74b8382af6c6a036aa7f47bf2/ghc >--------------------------------------------------------------- commit d7fbc6a33bd259b74b8382af6c6a036aa7f47bf2 Author: Ben Gamari Date: Sat Jun 3 17:02:01 2017 -0400 More debugging >--------------------------------------------------------------- d7fbc6a33bd259b74b8382af6c6a036aa7f47bf2 Jenkinsfile | 1 + 1 file changed, 1 insertion(+) diff --git a/Jenkinsfile b/Jenkinsfile index 151bc7b..dbc0e26 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -162,6 +162,7 @@ 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.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 From git at git.haskell.org Sat Jun 3 22:04:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Jun 2017 22:04:17 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: More debugging (fa1ef38) Message-ID: <20170603220417.B40B83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/fa1ef38be2a6846e2c6706a84345fcef51910803/ghc >--------------------------------------------------------------- commit fa1ef38be2a6846e2c6706a84345fcef51910803 Author: Ben Gamari Date: Sat Jun 3 17:02:01 2017 -0400 More debugging >--------------------------------------------------------------- fa1ef38be2a6846e2c6706a84345fcef51910803 Jenkinsfile | 2 ++ 1 file changed, 2 insertions(+) diff --git a/Jenkinsfile b/Jenkinsfile index 151bc7b..024f004 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -162,6 +162,8 @@ 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 From git at git.haskell.org Sat Jun 3 23:58:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Jun 2017 23:58:39 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: More debugging (17ec01e) Message-ID: <20170603235839.6D2413A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/17ec01e0b0de505d908a2e97c2866e85b63f6324/ghc >--------------------------------------------------------------- commit 17ec01e0b0de505d908a2e97c2866e85b63f6324 Author: Ben Gamari Date: Sat Jun 3 17:02:01 2017 -0400 More debugging >--------------------------------------------------------------- 17ec01e0b0de505d908a2e97c2866e85b63f6324 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 Sun Jun 4 01:33:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 01:33:26 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarName (06800cf) Message-ID: <20170604013326.9F7EE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/06800cf09c2834d44f9c10841b19ab493be0b0b8/ghc >--------------------------------------------------------------- commit 06800cf09c2834d44f9c10841b19ab493be0b0b8 Author: Ben Gamari Date: Sat Jun 3 21:33:12 2017 -0400 Fix tarName >--------------------------------------------------------------- 06800cf09c2834d44f9c10841b19ab493be0b0b8 Jenkinsfile | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index b40186c..5c02908 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("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 Sun Jun 4 03:11:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 03:11:20 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarName (397b069) Message-ID: <20170604031120.02D373A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/397b069ce995d5c6efd640b84e1b411d234169fb/ghc >--------------------------------------------------------------- commit 397b069ce995d5c6efd640b84e1b411d234169fb Author: Ben Gamari Date: Sat Jun 3 21:33:12 2017 -0400 Fix tarName >--------------------------------------------------------------- 397b069ce995d5c6efd640b84e1b411d234169fb 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 Sun Jun 4 05:02:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:02:33 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Actually call closure (4280ed5) Message-ID: <20170604050233.E0D4B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/4280ed51467ced22504d9709f46c58a121790e52/ghc >--------------------------------------------------------------- commit 4280ed51467ced22504d9709f46c58a121790e52 Author: Ben Gamari Date: Sun Jun 4 01:02:20 2017 -0400 Actually call closure >--------------------------------------------------------------- 4280ed51467ced22504d9709f46c58a121790e52 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 Sun Jun 4 05:07:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:08 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: More debugging (39a8227) Message-ID: <20170604050708.3903D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/39a82277a1d4054908739d56ef3d48e767e0dcbe/ghc >--------------------------------------------------------------- commit 39a82277a1d4054908739d56ef3d48e767e0dcbe Author: Ben Gamari Date: Sat Jun 3 17:02:01 2017 -0400 More debugging >--------------------------------------------------------------- 39a82277a1d4054908739d56ef3d48e767e0dcbe 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 Sun Jun 4 05:07:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:10 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Use archiveArtifacts instead of archive (ab22f5b) Message-ID: <20170604050710.E8A2C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ab22f5b7cbdd9a7bfe0f4fdae471a452b4d1620e/ghc >--------------------------------------------------------------- commit ab22f5b7cbdd9a7bfe0f4fdae471a452b4d1620e Author: Ben Gamari Date: Mon May 29 15:44:56 2017 -0400 Use archiveArtifacts instead of archive >--------------------------------------------------------------- ab22f5b7cbdd9a7bfe0f4fdae471a452b4d1620e 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 Sun Jun 4 05:07:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:16 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarName (63f0e16) Message-ID: <20170604050716.628E83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/63f0e168dbd6a76da8dce4f4a528da400f37ec54/ghc >--------------------------------------------------------------- commit 63f0e168dbd6a76da8dce4f4a528da400f37ec54 Author: Ben Gamari Date: Sat Jun 3 21:33:12 2017 -0400 Fix tarName >--------------------------------------------------------------- 63f0e168dbd6a76da8dce4f4a528da400f37ec54 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 Sun Jun 4 05:07:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:19 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Testing simpler Jenkinsfile (d1d48f1) Message-ID: <20170604050719.9A0E93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d1d48f129755877859774865e632afe7052c2601/ghc >--------------------------------------------------------------- commit d1d48f129755877859774865e632afe7052c2601 Author: Ben Gamari Date: Fri Apr 21 14:29:34 2017 -0400 Testing simpler Jenkinsfile >--------------------------------------------------------------- d1d48f129755877859774865e632afe7052c2601 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 Sun Jun 4 05:07:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:13 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix JSON serialization (f196062) Message-ID: <20170604050713.A6D8A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/f196062834d81a0fc0a9a1cb6351b68c3be2ec9c/ghc >--------------------------------------------------------------- commit f196062834d81a0fc0a9a1cb6351b68c3be2ec9c Author: Ben Gamari Date: Wed May 31 10:43:24 2017 -0400 Fix JSON serialization >--------------------------------------------------------------- f196062834d81a0fc0a9a1cb6351b68c3be2ec9c 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 Sun Jun 4 05:07:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:22 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Kill debugging (82ac131) Message-ID: <20170604050722.774AA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/82ac13138f0c26376528c84b639c3dded4703035/ghc >--------------------------------------------------------------- commit 82ac13138f0c26376528c84b639c3dded4703035 Author: Ben Gamari Date: Thu May 18 01:39:32 2017 -0400 Kill debugging >--------------------------------------------------------------- 82ac13138f0c26376528c84b639c3dded4703035 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 Sun Jun 4 05:07:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:25 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Hopefully fix Windows (a902185) Message-ID: <20170604050725.5AEC63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a902185ea5cfcd034f0e2d111826ff0d1f932cf8/ghc >--------------------------------------------------------------- commit a902185ea5cfcd034f0e2d111826ff0d1f932cf8 Author: Ben Gamari Date: Mon May 29 22:33:46 2017 -0400 Hopefully fix Windows >--------------------------------------------------------------- a902185ea5cfcd034f0e2d111826ff0d1f932cf8 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 Sun Jun 4 05:07:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:28 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (b060a51) Message-ID: <20170604050728.1E9CD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/b060a51c80004344e147d07b14c62ee0e166cd75/ghc >--------------------------------------------------------------- commit b060a51c80004344e147d07b14c62ee0e166cd75 Author: Ben Gamari Date: Thu May 18 02:59:40 2017 -0400 Debug >--------------------------------------------------------------- b060a51c80004344e147d07b14c62ee0e166cd75 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 Sun Jun 4 05:07:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:30 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix documentation (f28615c) Message-ID: <20170604050730.E103D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/f28615c330c137d1bfd36b9d7979140e59e8c5fb/ghc >--------------------------------------------------------------- commit f28615c330c137d1bfd36b9d7979140e59e8c5fb Author: Ben Gamari Date: Tue May 30 10:45:52 2017 -0400 Fix documentation >--------------------------------------------------------------- f28615c330c137d1bfd36b9d7979140e59e8c5fb 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 Sun Jun 4 05:07:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:33 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring, add Windows, fix cross (410859c) Message-ID: <20170604050733.B83373A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/410859cd0d9855e67a8de54658f5b38d209549c5/ghc >--------------------------------------------------------------- commit 410859cd0d9855e67a8de54658f5b38d209549c5 Author: Ben Gamari Date: Thu May 18 02:14:40 2017 -0400 Refactoring, add Windows, fix cross >--------------------------------------------------------------- 410859cd0d9855e67a8de54658f5b38d209549c5 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 Sun Jun 4 05:07:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:39 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Hmm (0cfcf87) Message-ID: <20170604050739.804633A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0cfcf877d9f6ba5a45d910519c7a82d36002a805/ghc >--------------------------------------------------------------- commit 0cfcf877d9f6ba5a45d910519c7a82d36002a805 Author: Ben Gamari Date: Mon May 29 16:45:16 2017 -0400 Hmm >--------------------------------------------------------------- 0cfcf877d9f6ba5a45d910519c7a82d36002a805 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 Sun Jun 4 05:07:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:36 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Be more explicit (473744f) Message-ID: <20170604050736.AF42D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/473744fee32368bad7f0bfd0639cd2b7314354bb/ghc >--------------------------------------------------------------- commit 473744fee32368bad7f0bfd0639cd2b7314354bb Author: Ben Gamari Date: Tue May 30 16:04:31 2017 -0400 Be more explicit >--------------------------------------------------------------- 473744fee32368bad7f0bfd0639cd2b7314354bb 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 Sun Jun 4 05:07:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:45 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Disable non-Windows builds (d2d183a) Message-ID: <20170604050745.09E893A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d2d183ab021b0827fc84412bb85e8dfebddcf78d/ghc >--------------------------------------------------------------- commit d2d183ab021b0827fc84412bb85e8dfebddcf78d Author: Ben Gamari Date: Mon May 29 19:34:11 2017 -0400 Disable non-Windows builds >--------------------------------------------------------------- d2d183ab021b0827fc84412bb85e8dfebddcf78d 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 Sun Jun 4 05:07:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:42 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Cross (16d2605) Message-ID: <20170604050742.455423A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/16d26051fa3839cb5bd1c45d62199484dfb6e7ee/ghc >--------------------------------------------------------------- commit 16d26051fa3839cb5bd1c45d62199484dfb6e7ee Author: Ben Gamari Date: Thu May 18 01:00:42 2017 -0400 Cross >--------------------------------------------------------------- 16d26051fa3839cb5bd1c45d62199484dfb6e7ee 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 Sun Jun 4 05:07:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:47 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Nailed the Windows issue (72baf64) Message-ID: <20170604050747.BFC353A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/72baf64cddc8feb2aafd572bfe944705cf318c90/ghc >--------------------------------------------------------------- commit 72baf64cddc8feb2aafd572bfe944705cf318c90 Author: Ben Gamari Date: Mon May 29 12:48:34 2017 -0400 Nailed the Windows issue >--------------------------------------------------------------- 72baf64cddc8feb2aafd572bfe944705cf318c90 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 Sun Jun 4 05:07:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:50 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Handle documentation (2aad0ec) Message-ID: <20170604050750.7B06F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2aad0ec6426b1aeb60f025899f13c30fcd3c31cd/ghc >--------------------------------------------------------------- commit 2aad0ec6426b1aeb60f025899f13c30fcd3c31cd Author: Ben Gamari Date: Tue May 30 01:46:06 2017 -0400 Handle documentation >--------------------------------------------------------------- 2aad0ec6426b1aeb60f025899f13c30fcd3c31cd 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 Sun Jun 4 05:07:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:53 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix Windows PATHs (dd0e251) Message-ID: <20170604050753.3B06B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/dd0e251d0f8e41c49c1962b20e20fb8a2cea502f/ghc >--------------------------------------------------------------- commit dd0e251d0f8e41c49c1962b20e20fb8a2cea502f Author: Ben Gamari Date: Mon May 29 16:31:28 2017 -0400 Fix Windows PATHs >--------------------------------------------------------------- dd0e251d0f8e41c49c1962b20e20fb8a2cea502f 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 Sun Jun 4 05:07:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:55 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Testing (5106252) Message-ID: <20170604050755.E40B43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/5106252c2aa3f257979dddaeef647ac552ec985a/ghc >--------------------------------------------------------------- commit 5106252c2aa3f257979dddaeef647ac552ec985a Author: Ben Gamari Date: Fri Apr 28 09:53:13 2017 -0400 Testing >--------------------------------------------------------------- 5106252c2aa3f257979dddaeef647ac552ec985a 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 Sun Jun 4 05:07:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:07:58 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (a8644ef) Message-ID: <20170604050758.A10CF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a8644efb055daa82465345cb47cb8f6a281b7995/ghc >--------------------------------------------------------------- commit a8644efb055daa82465345cb47cb8f6a281b7995 Author: Ben Gamari Date: Thu May 18 02:56:06 2017 -0400 Debug >--------------------------------------------------------------- a8644efb055daa82465345cb47cb8f6a281b7995 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 Sun Jun 4 05:08:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:01 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix missing binding (92fc96b) Message-ID: <20170604050801.655C23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/92fc96b62a72531343641290a9025a02a7d69dd9/ghc >--------------------------------------------------------------- commit 92fc96b62a72531343641290a9025a02a7d69dd9 Author: Ben Gamari Date: Wed May 31 11:36:00 2017 -0400 Fix missing binding >--------------------------------------------------------------- 92fc96b62a72531343641290a9025a02a7d69dd9 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 Sun Jun 4 05:08:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:04 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Reformat (a3a9dbe) Message-ID: <20170604050804.2B1F23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a3a9dbe5c9c8ccaf85baf577446d97a1439fa5f1/ghc >--------------------------------------------------------------- commit a3a9dbe5c9c8ccaf85baf577446d97a1439fa5f1 Author: Ben Gamari Date: Thu May 18 02:58:05 2017 -0400 Reformat >--------------------------------------------------------------- a3a9dbe5c9c8ccaf85baf577446d97a1439fa5f1 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 Sun Jun 4 05:08:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:06 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Run jobs in parallel (8824574) Message-ID: <20170604050806.D82753A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/8824574d55a7f8633da9270f0bcf1409dc6bda07/ghc >--------------------------------------------------------------- commit 8824574d55a7f8633da9270f0bcf1409dc6bda07 Author: Ben Gamari Date: Wed May 17 23:34:37 2017 -0400 Run jobs in parallel >--------------------------------------------------------------- 8824574d55a7f8633da9270f0bcf1409dc6bda07 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 Sun Jun 4 05:08:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:09 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Parametrize on make command (f7756fd) Message-ID: <20170604050809.94AC43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/f7756fd08a08e4a39d1e110ded48b44458ecb99f/ghc >--------------------------------------------------------------- commit f7756fd08a08e4a39d1e110ded48b44458ecb99f Author: Ben Gamari Date: Mon May 29 15:44:39 2017 -0400 Parametrize on make command >--------------------------------------------------------------- f7756fd08a08e4a39d1e110ded48b44458ecb99f 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 Sun Jun 4 05:08:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:12 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Reenable everything else (1b3397b) Message-ID: <20170604050812.4F7243A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/1b3397be9cf0787ead24e888c7f02f0162b6dcbf/ghc >--------------------------------------------------------------- commit 1b3397be9cf0787ead24e888c7f02f0162b6dcbf Author: Ben Gamari Date: Mon May 29 22:45:19 2017 -0400 Reenable everything else >--------------------------------------------------------------- 1b3397be9cf0787ead24e888c7f02f0162b6dcbf 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 Sun Jun 4 05:08:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:15 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix configure arguments (f1f835c) Message-ID: <20170604050815.0C8613A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/f1f835c14a46cac8c1e867e0193f5545f5657fd1/ghc >--------------------------------------------------------------- commit f1f835c14a46cac8c1e867e0193f5545f5657fd1 Author: Ben Gamari Date: Mon May 29 22:55:51 2017 -0400 Fix configure arguments >--------------------------------------------------------------- f1f835c14a46cac8c1e867e0193f5545f5657fd1 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 Sun Jun 4 05:08:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:17 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Don't run nofib on Windows (26218fc) Message-ID: <20170604050817.BEBEF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/26218fc37ff8ab53dd088f2bca04231d80de65ac/ghc >--------------------------------------------------------------- commit 26218fc37ff8ab53dd088f2bca04231d80de65ac Author: Ben Gamari Date: Mon May 29 16:14:11 2017 -0400 Don't run nofib on Windows >--------------------------------------------------------------- 26218fc37ff8ab53dd088f2bca04231d80de65ac 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 Sun Jun 4 05:08:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:20 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Checkout (6ca7028) Message-ID: <20170604050820.812A73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/6ca702827a7587282bf32e9def039849d4f68c95/ghc >--------------------------------------------------------------- commit 6ca702827a7587282bf32e9def039849d4f68c95 Author: Ben Gamari Date: Thu May 18 01:19:52 2017 -0400 Checkout >--------------------------------------------------------------- 6ca702827a7587282bf32e9def039849d4f68c95 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 Sun Jun 4 05:08:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:23 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Clean up treatment of tests (2eee427) Message-ID: <20170604050823.458383A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2eee427fdacc62750cbe17725364e68d37ef54f0/ghc >--------------------------------------------------------------- commit 2eee427fdacc62750cbe17725364e68d37ef54f0 Author: Ben Gamari Date: Tue May 30 01:10:56 2017 -0400 Clean up treatment of tests >--------------------------------------------------------------- 2eee427fdacc62750cbe17725364e68d37ef54f0 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 Sun Jun 4 05:08:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:26 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: More things (2c29890) Message-ID: <20170604050826.05C7A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2c2989067974918b1122ae57b720bcd47c166271/ghc >--------------------------------------------------------------- commit 2c2989067974918b1122ae57b720bcd47c166271 Author: Ben Gamari Date: Thu May 18 01:38:55 2017 -0400 More things >--------------------------------------------------------------- 2c2989067974918b1122ae57b720bcd47c166271 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 Sun Jun 4 05:08:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:28 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix testsuite (0ca1b1f) Message-ID: <20170604050828.B8C773A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0ca1b1ff8981b2ef46a67ccf3c15a3c886ebb2cd/ghc >--------------------------------------------------------------- commit 0ca1b1ff8981b2ef46a67ccf3c15a3c886ebb2cd Author: Ben Gamari Date: Tue May 30 12:11:16 2017 -0400 Fix testsuite >--------------------------------------------------------------- 0ca1b1ff8981b2ef46a67ccf3c15a3c886ebb2cd 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 Sun Jun 4 05:08:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:31 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Move to scripted pipeline (be7baab) Message-ID: <20170604050831.7CEC83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/be7baabd9c207d939b6ac22970d0549ea04da295/ghc >--------------------------------------------------------------- commit be7baabd9c207d939b6ac22970d0549ea04da295 Author: Ben Gamari Date: Wed May 17 20:52:58 2017 -0400 Move to scripted pipeline >--------------------------------------------------------------- be7baabd9c207d939b6ac22970d0549ea04da295 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 Sun Jun 4 05:08:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:34 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (fa8ea54) Message-ID: <20170604050834.3F61A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/fa8ea54027e75b714a9ffff6bed507a1d5c5bf07/ghc >--------------------------------------------------------------- commit fa8ea54027e75b714a9ffff6bed507a1d5c5bf07 Author: Ben Gamari Date: Wed May 17 23:42:59 2017 -0400 Debug >--------------------------------------------------------------- fa8ea54027e75b714a9ffff6bed507a1d5c5bf07 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 Sun Jun 4 05:08:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:36 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring (708d38e) Message-ID: <20170604050836.F21923A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/708d38e9bc1ecd18d325b8ba204f6fcb4488b49b/ghc >--------------------------------------------------------------- commit 708d38e9bc1ecd18d325b8ba204f6fcb4488b49b Author: Ben Gamari Date: Wed May 17 20:20:55 2017 -0400 Refactoring >--------------------------------------------------------------- 708d38e9bc1ecd18d325b8ba204f6fcb4488b49b 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 Sun Jun 4 05:08:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:39 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Disable large address space on FreeBSD (f664462) Message-ID: <20170604050839.B7E883A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/f664462dfabaae15aabd1b41fff5fa7e58ceda7a/ghc >--------------------------------------------------------------- commit f664462dfabaae15aabd1b41fff5fa7e58ceda7a Author: Ben Gamari Date: Mon May 29 16:34:26 2017 -0400 Disable large address space on FreeBSD >--------------------------------------------------------------- f664462dfabaae15aabd1b41fff5fa7e58ceda7a 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 Sun Jun 4 05:08:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:42 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (9acac53) Message-ID: <20170604050842.7D5423A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9acac5315fdf45bce0daf4e602c9e02b8ef15f7e/ghc >--------------------------------------------------------------- commit 9acac5315fdf45bce0daf4e602c9e02b8ef15f7e Author: Ben Gamari Date: Mon May 29 15:49:33 2017 -0400 Debug >--------------------------------------------------------------- 9acac5315fdf45bce0daf4e602c9e02b8ef15f7e 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 Sun Jun 4 05:08:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:45 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: windows (712e810) Message-ID: <20170604050845.3885B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/712e810c2f81acdbf41af5da2ea9a2526ad0304a/ghc >--------------------------------------------------------------- commit 712e810c2f81acdbf41af5da2ea9a2526ad0304a Author: Ben Gamari Date: Thu May 18 01:55:46 2017 -0400 windows >--------------------------------------------------------------- 712e810c2f81acdbf41af5da2ea9a2526ad0304a 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 Sun Jun 4 05:08:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:47 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (a2c0c49) Message-ID: <20170604050847.EA64E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a2c0c496c2c813651dc95e867bac953b435531a1/ghc >--------------------------------------------------------------- commit a2c0c496c2c813651dc95e867bac953b435531a1 Author: Ben Gamari Date: Wed May 31 14:57:34 2017 -0400 Debug >--------------------------------------------------------------- a2c0c496c2c813651dc95e867bac953b435531a1 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 Sun Jun 4 05:08:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:50 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Try again (b473826) Message-ID: <20170604050850.A81F43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/b4738269a94747d7c40d4c8809e17c5d54ed959c/ghc >--------------------------------------------------------------- commit b4738269a94747d7c40d4c8809e17c5d54ed959c Author: Ben Gamari Date: Mon May 29 16:42:42 2017 -0400 Try again >--------------------------------------------------------------- b4738269a94747d7c40d4c8809e17c5d54ed959c 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 Sun Jun 4 05:08:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:53 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add nofib, bindist, and aarch64 support (62edfc5) Message-ID: <20170604050853.616E93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/62edfc5991d5e39551f01f4608509d9e222190f3/ghc >--------------------------------------------------------------- commit 62edfc5991d5e39551f01f4608509d9e222190f3 Author: Ben Gamari Date: Wed May 17 22:41:02 2017 -0400 Add nofib, bindist, and aarch64 support >--------------------------------------------------------------- 62edfc5991d5e39551f01f4608509d9e222190f3 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 Sun Jun 4 05:08:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:56 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Actually call closure (db42b40) Message-ID: <20170604050856.1AF713A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/db42b4083cbc40561eecf6d53613e1cb0e217756/ghc >--------------------------------------------------------------- commit db42b4083cbc40561eecf6d53613e1cb0e217756 Author: Ben Gamari Date: Sun Jun 4 01:02:20 2017 -0400 Actually call closure >--------------------------------------------------------------- db42b4083cbc40561eecf6d53613e1cb0e217756 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 Sun Jun 4 05:08:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:08:58 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix test (10d08f0) Message-ID: <20170604050858.D17D23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/10d08f0e8b256b3d7d40a55d9c47019ca4780502/ghc >--------------------------------------------------------------- commit 10d08f0e8b256b3d7d40a55d9c47019ca4780502 Author: Ben Gamari Date: Tue May 30 13:57:23 2017 -0400 Fix test >--------------------------------------------------------------- 10d08f0e8b256b3d7d40a55d9c47019ca4780502 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 Sun Jun 4 05:09:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:09:01 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Clean (f84866c) Message-ID: <20170604050901.8F14A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/f84866c3aabe124e13b4813552c0c9538fa756ed/ghc >--------------------------------------------------------------- commit f84866c3aabe124e13b4813552c0c9538fa756ed Author: Ben Gamari Date: Tue May 30 00:29:29 2017 -0400 Clean >--------------------------------------------------------------- f84866c3aabe124e13b4813552c0c9538fa756ed 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 Sun Jun 4 05:09:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:09:04 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rework handling of Windows (9644daf) Message-ID: <20170604050904.4B7063A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9644daf6d5b5b70bc7c28bd933bd3014d6a9f62f/ghc >--------------------------------------------------------------- commit 9644daf6d5b5b70bc7c28bd933bd3014d6a9f62f Author: Ben Gamari Date: Mon May 29 13:08:49 2017 -0400 Rework handling of Windows >--------------------------------------------------------------- 9644daf6d5b5b70bc7c28bd933bd3014d6a9f62f 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 Sun Jun 4 05:09:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:09:07 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarball generation (3fe9ec3) Message-ID: <20170604050907.0DF163A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/3fe9ec362951e2d64419ba8e73c51300cdb371e6/ghc >--------------------------------------------------------------- commit 3fe9ec362951e2d64419ba8e73c51300cdb371e6 Author: Ben Gamari Date: Tue May 30 10:43:09 2017 -0400 Fix tarball generation >--------------------------------------------------------------- 3fe9ec362951e2d64419ba8e73c51300cdb371e6 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 Sun Jun 4 05:09:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:09:09 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Unregisterised (3019767) Message-ID: <20170604050909.BB26C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/30197671df3dbdeb6289b9f8bd8e2fc5bb1c8768/ghc >--------------------------------------------------------------- commit 30197671df3dbdeb6289b9f8bd8e2fc5bb1c8768 Author: Ben Gamari Date: Thu May 18 01:55:35 2017 -0400 Unregisterised >--------------------------------------------------------------- 30197671df3dbdeb6289b9f8bd8e2fc5bb1c8768 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 Sun Jun 4 05:09:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:09:12 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix FreeBSD architecture (afeb924) Message-ID: <20170604050912.7653E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/afeb924147d566f5035fdd81bbe35bf4ee10dccf/ghc >--------------------------------------------------------------- commit afeb924147d566f5035fdd81bbe35bf4ee10dccf Author: Ben Gamari Date: Mon May 29 13:55:03 2017 -0400 Fix FreeBSD architecture >--------------------------------------------------------------- afeb924147d566f5035fdd81bbe35bf4ee10dccf 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 Sun Jun 4 05:09:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:09:15 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add THREADS parameter (caf1132) Message-ID: <20170604050915.2DC413A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/caf1132695bf60125b7d0f49e0e0b817304a0e33/ghc >--------------------------------------------------------------- commit caf1132695bf60125b7d0f49e0e0b817304a0e33 Author: Ben Gamari Date: Sat May 13 11:59:37 2017 -0400 Add THREADS parameter >--------------------------------------------------------------- caf1132695bf60125b7d0f49e0e0b817304a0e33 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 Sun Jun 4 05:09:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 05:09:18 +0000 (UTC) Subject: [commit: ghc] wip/jenkins's head updated: Actually call closure (db42b40) Message-ID: <20170604050918.70D423A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/jenkins' now includes: 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 d1d48f1 Testing simpler Jenkinsfile 5106252 Testing caf1132 Add THREADS parameter 708d38e Refactoring be7baab Move to scripted pipeline 62edfc5 Add nofib, bindist, and aarch64 support 8824574 Run jobs in parallel fa8ea54 Debug 16d2605 Cross 6ca7028 Checkout 2c29890 More things 82ac131 Kill debugging 3019767 Unregisterised 712e810 windows 410859c Refactoring, add Windows, fix cross a8644ef Debug a3a9dbe Reformat b060a51 Debug 72baf64 Nailed the Windows issue 9644daf Rework handling of Windows afeb924 Fix FreeBSD architecture f7756fd Parametrize on make command ab22f5b Use archiveArtifacts instead of archive 9acac53 Debug 26218fc Don't run nofib on Windows dd0e251 Fix Windows PATHs f664462 Disable large address space on FreeBSD b473826 Try again 0cfcf87 Hmm d2d183a Disable non-Windows builds a902185 Hopefully fix Windows 1b3397b Reenable everything else f1f835c Fix configure arguments f84866c Clean 2eee427 Clean up treatment of tests 2aad0ec Handle documentation 3fe9ec3 Fix tarball generation f28615c Fix documentation 0ca1b1f Fix testsuite 10d08f0 Fix test 473744f Be more explicit f196062 Fix JSON serialization 92fc96b Fix missing binding a2c0c49 Debug 39a8227 More debugging 63f0e16 Fix tarName db42b40 Actually call closure From git at git.haskell.org Sun Jun 4 14:18:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 14:18:01 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Build from source distribution (8692edf) Message-ID: <20170604141801.157903A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/8692edfce59b58dba274978ae30182be09292f80/ghc >--------------------------------------------------------------- commit 8692edfce59b58dba274978ae30182be09292f80 Author: Ben Gamari Date: Mon May 29 13:55:58 2017 -0400 Build from source distribution >--------------------------------------------------------------- 8692edfce59b58dba274978ae30182be09292f80 Jenkinsfile | 173 +++++++++++++++++++++++++++++++++++++----------------------- 1 file changed, 108 insertions(+), 65 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index fa710c3..2315187 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -18,6 +18,25 @@ properties( ]) ]) + +stage("Build source distribution") { + node(label: 'linux') { + checkout scm + sh "git submodule update --init --recursive" + sh """ + ./boot + ./configure + mk/get-win32-tarballs.sh fetch all + 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 +122,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 +189,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 +200,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 Sun Jun 4 14:22:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 14:22:47 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Build from source distribution (5fb4809) Message-ID: <20170604142247.BD4E73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/5fb4809c9c077ed67ec9762f633767d7db58cfa5/ghc >--------------------------------------------------------------- commit 5fb4809c9c077ed67ec9762f633767d7db58cfa5 Author: Ben Gamari Date: Mon May 29 13:55:58 2017 -0400 Build from source distribution >--------------------------------------------------------------- 5fb4809c9c077ed67ec9762f633767d7db58cfa5 Jenkinsfile | 183 +++++++++++++++++++++++++++++++++++++++--------------------- 1 file changed, 118 insertions(+), 65 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index fa710c3..7783f11 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -18,6 +18,35 @@ 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 +132,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 +199,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 +210,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 Sun Jun 4 14:35:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 14:35:09 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Build from source distribution (73a4bf8) Message-ID: <20170604143509.E24573A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/73a4bf8f31d72ca8663982387c7eec26fecff484/ghc >--------------------------------------------------------------- commit 73a4bf8f31d72ca8663982387c7eec26fecff484 Author: Ben Gamari Date: Mon May 29 13:55:58 2017 -0400 Build from source distribution >--------------------------------------------------------------- 73a4bf8f31d72ca8663982387c7eec26fecff484 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 Sun Jun 4 14:35:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 14:35:12 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Introduce echo! make target (8d76df0) Message-ID: <20170604143512.A2F2E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/8d76df0f6e622f1dd3db934362392d01918599e5/ghc >--------------------------------------------------------------- commit 8d76df0f6e622f1dd3db934362392d01918599e5 Author: Ben Gamari Date: Sun Jun 4 10:27:24 2017 -0400 Introduce echo! make target This is analogous to show! >--------------------------------------------------------------- 8d76df0f6e622f1dd3db934362392d01918599e5 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 3fafcf0..dd9d8b6 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 Sun Jun 4 14:35:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 14:35:15 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarball names (6b1cf5e) Message-ID: <20170604143515.7216B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/6b1cf5e74c4c996ac5f42abcebc25dfa723e11f2/ghc >--------------------------------------------------------------- commit 6b1cf5e74c4c996ac5f42abcebc25dfa723e11f2 Author: Ben Gamari Date: Sun Jun 4 10:34:37 2017 -0400 Fix tarball names >--------------------------------------------------------------- 6b1cf5e74c4c996ac5f42abcebc25dfa723e11f2 Jenkinsfile | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 3b31238..94938d8 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}.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 Sun Jun 4 14:37:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 14:37:49 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarball names (4012478) Message-ID: <20170604143749.709463A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/40124788f8f62eb92a64b3ae59ca6d129f6285ae/ghc >--------------------------------------------------------------- commit 40124788f8f62eb92a64b3ae59ca6d129f6285ae Author: Ben Gamari Date: Sun Jun 4 10:34:37 2017 -0400 Fix tarball names >--------------------------------------------------------------- 40124788f8f62eb92a64b3ae59ca6d129f6285ae Jenkinsfile | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 3b31238..b4e6876 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 Sun Jun 4 14:40:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 14:40:19 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarball names (cb0a48a) Message-ID: <20170604144019.2B56A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/cb0a48a3522c926d0234ac1e1e80c9d9ce23c1d9/ghc >--------------------------------------------------------------- commit cb0a48a3522c926d0234ac1e1e80c9d9ce23c1d9 Author: Ben Gamari Date: Sun Jun 4 10:34:37 2017 -0400 Fix tarball names >--------------------------------------------------------------- cb0a48a3522c926d0234ac1e1e80c9d9ce23c1d9 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 Sun Jun 4 14:47:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 14:47:41 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: No need to configure (5d657e5) Message-ID: <20170604144741.E2E323A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/5d657e5f1d72a3a00b1d1c2897f46787534656b0/ghc >--------------------------------------------------------------- commit 5d657e5f1d72a3a00b1d1c2897f46787534656b0 Author: Ben Gamari Date: Sun Jun 4 10:47:30 2017 -0400 No need to configure >--------------------------------------------------------------- 5d657e5f1d72a3a00b1d1c2897f46787534656b0 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 Sun Jun 4 14:52:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 14:52:18 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: A bit more paranoia around directory deletion (d580f6d) Message-ID: <20170604145218.494EA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d580f6d8e60875c47dd2fd187603140a878e172e/ghc >--------------------------------------------------------------- commit d580f6d8e60875c47dd2fd187603140a878e172e 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. >--------------------------------------------------------------- d580f6d8e60875c47dd2fd187603140a878e172e 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 Sun Jun 4 14:55:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 14:55:02 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: No need to boot (a5acb58) Message-ID: <20170604145502.11CBF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a5acb5893f6231903dd61218df1a0f55ba5d5b62/ghc >--------------------------------------------------------------- commit a5acb5893f6231903dd61218df1a0f55ba5d5b62 Author: Ben Gamari Date: Sun Jun 4 10:54:49 2017 -0400 No need to boot >--------------------------------------------------------------- a5acb5893f6231903dd61218df1a0f55ba5d5b62 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 Sun Jun 4 15:06:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 15:06:30 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Trim whitespace from git output (d0f51f4) Message-ID: <20170604150630.70B403A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d0f51f4061363fbbc884705c2372dba213bbb4e2/ghc >--------------------------------------------------------------- commit d0f51f4061363fbbc884705c2372dba213bbb4e2 Author: Ben Gamari Date: Sun Jun 4 11:00:28 2017 -0400 Trim whitespace from git output >--------------------------------------------------------------- d0f51f4061363fbbc884705c2372dba213bbb4e2 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 Sun Jun 4 15:06:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 15:06:33 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix source directory name (9833a2e) Message-ID: <20170604150633.2CD7B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9833a2ec46b319d5123a3d01ac614dbad1580ca7/ghc >--------------------------------------------------------------- commit 9833a2ec46b319d5123a3d01ac614dbad1580ca7 Author: Ben Gamari Date: Sun Jun 4 11:06:15 2017 -0400 Fix source directory name >--------------------------------------------------------------- 9833a2ec46b319d5123a3d01ac614dbad1580ca7 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 Sun Jun 4 15:12:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 15:12:34 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debuggging (0088909) Message-ID: <20170604151234.B24473A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0088909c66f6c12c585705f67a3ff381d9d97ecf/ghc >--------------------------------------------------------------- commit 0088909c66f6c12c585705f67a3ff381d9d97ecf Author: Ben Gamari Date: Sun Jun 4 11:12:23 2017 -0400 Debuggging >--------------------------------------------------------------- 0088909c66f6c12c585705f67a3ff381d9d97ecf 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 Sun Jun 4 15:18:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 15:18:35 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (bbc2b22) Message-ID: <20170604151835.4C01E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/bbc2b22a8417bb026c018f49c6b7c36c7c3a58b7/ghc >--------------------------------------------------------------- commit bbc2b22a8417bb026c018f49c6b7c36c7c3a58b7 Author: Ben Gamari Date: Sun Jun 4 11:18:23 2017 -0400 Debug >--------------------------------------------------------------- bbc2b22a8417bb026c018f49c6b7c36c7c3a58b7 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 Sun Jun 4 15:27:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 15:27:07 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Try adding type annotation (9419f42) Message-ID: <20170604152707.81C513A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9419f4271f14f0d03de856044ab8c749531af37d/ghc >--------------------------------------------------------------- commit 9419f4271f14f0d03de856044ab8c749531af37d Author: Ben Gamari Date: Sun Jun 4 11:26:54 2017 -0400 Try adding type annotation >--------------------------------------------------------------- 9419f4271f14f0d03de856044ab8c749531af37d 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 Sun Jun 4 15:32:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 15:32:18 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (ec8f586) Message-ID: <20170604153218.7EF5D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ec8f586f9549e96be8cfa1e0ab69fd9b4cee6eb3/ghc >--------------------------------------------------------------- commit ec8f586f9549e96be8cfa1e0ab69fd9b4cee6eb3 Author: Ben Gamari Date: Sun Jun 4 11:32:08 2017 -0400 Debug >--------------------------------------------------------------- ec8f586f9549e96be8cfa1e0ab69fd9b4cee6eb3 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 Sun Jun 4 16:32:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 16:32:50 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rip out debug output (dc230c0) Message-ID: <20170604163250.68E8B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/dc230c01feaed8e87d46f7a33f8dc071234e505c/ghc >--------------------------------------------------------------- commit dc230c01feaed8e87d46f7a33f8dc071234e505c Author: Ben Gamari Date: Sun Jun 4 11:36:21 2017 -0400 Rip out debug output >--------------------------------------------------------------- dc230c01feaed8e87d46f7a33f8dc071234e505c 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 Sun Jun 4 16:32:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 16:32:53 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: bindist: Compress with threaded xz by default (e291ae0) Message-ID: <20170604163253.1E51B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/e291ae02f5c04cfee9de8b2f1633162be886008e/ghc >--------------------------------------------------------------- commit e291ae02f5c04cfee9de8b2f1633162be886008e Author: Ben Gamari Date: Sun Jun 4 12:19:13 2017 -0400 bindist: Compress with threaded xz by default >--------------------------------------------------------------- e291ae02f5c04cfee9de8b2f1633162be886008e 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 189439e..044c928 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -794,7 +794,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 Sun Jun 4 16:32:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 16:32:55 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Configure bindist (099cb42) Message-ID: <20170604163255.C9B943A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/099cb42d62e8140c213645915e26eb242b158e19/ghc >--------------------------------------------------------------- commit 099cb42d62e8140c213645915e26eb242b158e19 Author: Ben Gamari Date: Sun Jun 4 12:32:40 2017 -0400 Configure bindist >--------------------------------------------------------------- 099cb42d62e8140c213645915e26eb242b158e19 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 Sun Jun 4 19:56:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Jun 2017 19:56:51 +0000 (UTC) Subject: [commit: ghc] wip/new-tree-one-param-2: Udate hsSyn AST to use Trees that Grow (46af88c) Message-ID: <20170604195651.92C3F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-tree-one-param-2 Link : http://ghc.haskell.org/trac/ghc/changeset/46af88c257d4aab8912690a0b1d3ab038f160e1d/ghc >--------------------------------------------------------------- commit 46af88c257d4aab8912690a0b1d3ab038f160e1d Author: Alan Zimmerman Date: Fri May 19 14:56:09 2017 +0200 Udate hsSyn AST to use Trees that Grow Summary: See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow This commit prepares the ground for a full extensible AST, by replacing the type parameter for the hsSyn data types with a set of indices into type families, data GhcPs -- ^ Index for GHC parser output data GhcRn -- ^ Index for GHC renamer output data GhcTc -- ^ Index for GHC typechecker output These are now used instead of `RdrName`, `Name` and `Id`/`TcId`/`Var` Where the original name type is required in a polymorphic context, this is accessible via the IdP type family, defined as type family IdP p type instance IdP GhcPs = RdrName type instance IdP GhcRn = Name type instance IdP GhcTc = Id These types are declared in the new 'hsSyn/HsExtension.hs' module. To gain a better understanding of the extension mechanism, it has been applied to `HsLit` only, also replacing the `SourceText` fields in them with extension types. To preserve extension generality, a type class is introduced to capture the `SourceText` interface, which must be honoured by all of the extension points which originally had a `SourceText`. The class is defined as class HasSourceText a where -- Provide setters to mimic existing constructors noSourceText :: a sourceText :: String -> a setSourceText :: SourceText -> a getSourceText :: a -> SourceText And the constraint is captured in `SourceTextX`, which is a constraint type listing all the extension points that make use of the class. Updating Haddock submodule to match. Test Plan: ./validate Reviewers: simonpj, shayan-najd, goldfire, austin, bgamari Subscribers: rwbarton, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D3609 >--------------------------------------------------------------- 46af88c257d4aab8912690a0b1d3ab038f160e1d compiler/backpack/BkpSyn.hs | 3 +- compiler/backpack/DriverBkp.hs | 4 +- compiler/deSugar/Check.hs | 66 +-- compiler/deSugar/Coverage.hs | 122 ++--- compiler/deSugar/Desugar.hs | 7 +- compiler/deSugar/DsArrows.hs | 71 +-- compiler/deSugar/DsBinds.hs | 16 +- compiler/deSugar/DsExpr.hs | 41 +- compiler/deSugar/DsExpr.hs-boot | 16 +- compiler/deSugar/DsForeign.hs | 10 +- compiler/deSugar/DsGRHSs.hs | 18 +- compiler/deSugar/DsListComp.hs | 59 +-- compiler/deSugar/DsMeta.hs | 231 ++++----- compiler/deSugar/DsMonad.hs | 2 +- compiler/deSugar/DsUtils.hs | 29 +- compiler/deSugar/Match.hs | 43 +- compiler/deSugar/Match.hs-boot | 9 +- compiler/deSugar/MatchCon.hs | 8 +- compiler/deSugar/MatchLit.hs | 40 +- compiler/deSugar/PmExpr.hs | 12 +- compiler/ghc.cabal.in | 1 + compiler/ghc.mk | 1 + compiler/hsSyn/Convert.hs | 149 +++--- compiler/hsSyn/HsBinds.hs | 121 ++--- compiler/hsSyn/HsDecls.hs | 531 +++++++++++---------- compiler/hsSyn/HsDumpAst.hs | 28 +- compiler/hsSyn/HsExpr.hs | 461 +++++++++--------- compiler/hsSyn/HsExpr.hs-boot | 40 +- compiler/hsSyn/HsExtension.hs | 289 +++++++++++ compiler/hsSyn/HsImpExp.hs | 37 +- compiler/hsSyn/HsLit.hs | 132 +++-- compiler/hsSyn/HsPat.hs | 183 +++---- compiler/hsSyn/HsPat.hs-boot | 6 +- compiler/hsSyn/HsSyn.hs | 7 +- compiler/hsSyn/HsTypes.hs | 392 +++++++-------- compiler/hsSyn/HsUtils.hs | 297 ++++++------ compiler/hsSyn/PlaceHolder.hs | 50 -- compiler/main/GHC.hs | 8 +- compiler/main/HeaderInfo.hs | 7 +- compiler/main/Hooks.hs | 28 +- compiler/main/HscMain.hs | 16 +- compiler/main/HscStats.hs | 3 +- compiler/main/HscTypes.hs | 34 +- compiler/main/InteractiveEval.hs | 10 +- compiler/parser/Parser.y | 373 ++++++++------- compiler/parser/RdrHsSyn.hs | 245 +++++----- compiler/rename/RnBinds.hs | 150 +++--- compiler/rename/RnEnv.hs | 29 +- compiler/rename/RnExpr.hs | 226 ++++----- compiler/rename/RnExpr.hs-boot | 22 +- compiler/rename/RnFixity.hs | 2 +- compiler/rename/RnNames.hs | 87 ++-- compiler/rename/RnPat.hs | 64 +-- compiler/rename/RnSource.hs | 187 ++++---- compiler/rename/RnSplice.hs | 63 +-- compiler/rename/RnSplice.hs-boot | 12 +- compiler/rename/RnTypes.hs | 211 ++++---- compiler/rename/RnUtils.hs | 2 +- compiler/typecheck/Inst.hs | 29 +- compiler/typecheck/TcAnnotations.hs | 17 +- compiler/typecheck/TcArrows.hs | 19 +- compiler/typecheck/TcBackpack.hs | 1 + compiler/typecheck/TcBinds.hs | 96 ++-- compiler/typecheck/TcClassDcl.hs | 41 +- compiler/typecheck/TcDefaults.hs | 8 +- compiler/typecheck/TcDeriv.hs | 39 +- compiler/typecheck/TcDerivUtils.hs | 8 +- compiler/typecheck/TcEnv.hs | 18 +- compiler/typecheck/TcEnv.hs-boot | 1 + compiler/typecheck/TcExpr.hs | 146 +++--- compiler/typecheck/TcExpr.hs-boot | 31 +- compiler/typecheck/TcForeign.hs | 23 +- compiler/typecheck/TcGenDeriv.hs | 151 +++--- compiler/typecheck/TcGenFunctor.hs | 99 ++-- compiler/typecheck/TcGenGenerics.hs | 32 +- compiler/typecheck/TcHsSyn.hs | 137 +++--- compiler/typecheck/TcHsType.hs | 93 ++-- compiler/typecheck/TcInstDcls.hs | 72 +-- compiler/typecheck/TcInstDcls.hs-boot | 5 +- compiler/typecheck/TcMatches.hs | 106 ++-- compiler/typecheck/TcMatches.hs-boot | 11 +- compiler/typecheck/TcPat.hs | 53 +- compiler/typecheck/TcPatSyn.hs | 86 ++-- compiler/typecheck/TcPatSyn.hs-boot | 13 +- compiler/typecheck/TcRnDriver.hs | 63 +-- compiler/typecheck/TcRnExports.hs | 41 +- compiler/typecheck/TcRnTypes.hs | 73 +-- compiler/typecheck/TcRules.hs | 10 +- compiler/typecheck/TcSigs.hs | 34 +- compiler/typecheck/TcSplice.hs | 53 +- compiler/typecheck/TcSplice.hs-boot | 36 +- compiler/typecheck/TcTyClsDecls.hs | 112 ++--- compiler/typecheck/TcTyDecls.hs | 11 +- compiler/typecheck/TcTypeable.hs | 55 +-- compiler/typecheck/TcUnify.hs | 11 +- compiler/typecheck/TcUnify.hs-boot | 14 +- compiler/typecheck/TcValidity.hs | 2 +- docs/users_guide/8.4.1-notes.rst | 34 ++ ghc/GHCi/UI.hs | 6 +- ghc/GHCi/UI/Info.hs | 6 +- ghc/GHCi/UI/Monad.hs | 7 +- .../tests/ghc-api/annotations-literals/parsed.hs | 6 +- testsuite/tests/ghc-api/annotations/parseTree.hs | 2 +- .../tests/ghc-api/annotations/stringSource.hs | 6 +- testsuite/tests/ghc-api/annotations/t11430.hs | 4 +- testsuite/tests/quasiquotation/T7918.hs | 6 +- utils/ghctags/Main.hs | 5 +- utils/haddock | 2 +- 108 files changed, 3917 insertions(+), 3328 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 46af88c257d4aab8912690a0b1d3ab038f160e1d From git at git.haskell.org Mon Jun 5 08:43:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jun 2017 08:43:22 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #13784 (6597f08) Message-ID: <20170605084322.718CC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6597f0846904dc5accbe2556badbd29a8a58c28e/ghc >--------------------------------------------------------------- commit 6597f0846904dc5accbe2556badbd29a8a58c28e Author: Simon Peyton Jones Date: Mon Jun 5 09:43:05 2017 +0100 Test Trac #13784 >--------------------------------------------------------------- 6597f0846904dc5accbe2556badbd29a8a58c28e .../tests/indexed-types/should_fail/T13784.hs | 30 +++++++++++++++ .../tests/indexed-types/should_fail/T13784.stderr | 44 ++++++++++++++++++++++ testsuite/tests/indexed-types/should_fail/all.T | 1 + 3 files changed, 75 insertions(+) diff --git a/testsuite/tests/indexed-types/should_fail/T13784.hs b/testsuite/tests/indexed-types/should_fail/T13784.hs new file mode 100644 index 0000000..0a0ae04 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T13784.hs @@ -0,0 +1,30 @@ +{-# LANGUAGE DataKinds, FlexibleContexts, FlexibleInstances, GADTs #-} +{-# LANGUAGE KindSignatures, MultiParamTypeClasses, TypeFamilies, TypeOperators #-} + +module T13784 where + +import Data.Monoid ((<>)) + +data Product :: [*] -> * where + (:*) :: a -> Product as -> Product (a : as) + Unit :: Product '[] +infixr 5 :* + +instance Show (Product '[]) where + show Unit = "Unit" + +instance (Show a, Show (Product as)) => Show (Product (a : as)) where + show (a :* as) = show a <> " :* " <> show as + +class Divideable a as where + type Divide a as :: [*] + divide :: Product as -> (a, Product (Divide a as)) + +instance Divideable a (a : as) where + -- type Divide a (a : as) = as + -- Conflicting type family instances, seems like OVERLAPS isn't a thing for type families. + divide (a :* as) = (a, as) + +instance Divideable b as => Divideable b (a : as) where + type Divide b (a : as) = a : Divide b as + divide (a :* as) = a :* divide as diff --git a/testsuite/tests/indexed-types/should_fail/T13784.stderr b/testsuite/tests/indexed-types/should_fail/T13784.stderr new file mode 100644 index 0000000..547809c --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T13784.stderr @@ -0,0 +1,44 @@ + +T13784.hs:26:28: error: + • Could not deduce: as1 ~ (a1 : Divide a1 as1) + from the context: (a : as) ~ (a1 : as1) + bound by a pattern with constructor: + :* :: forall a (as :: [*]). a -> Product as -> Product (a : as), + in an equation for ‘divide’ + at T13784.hs:26:13-19 + ‘as1’ is a rigid type variable bound by + a pattern with constructor: + :* :: forall a (as :: [*]). a -> Product as -> Product (a : as), + in an equation for ‘divide’ + at T13784.hs:26:13-19 + Expected type: Product (Divide a (a : as)) + Actual type: Product as1 + • In the expression: as + In the expression: (a, as) + In an equation for ‘divide’: divide (a :* as) = (a, as) + • Relevant bindings include + as :: Product as1 (bound at T13784.hs:26:18) + a :: a1 (bound at T13784.hs:26:13) + +T13784.hs:30:24: error: + • Couldn't match type ‘Product (a1 : as0)’ + with ‘(b, Product (Divide b (a1 : as1)))’ + Expected type: (b, Product (Divide b (a : as))) + Actual type: Product (a1 : as0) + • In the expression: a :* divide as + In an equation for ‘divide’: divide (a :* as) = a :* divide as + In the instance declaration for ‘Divideable b (a : as)’ + • Relevant bindings include + as :: Product as1 (bound at T13784.hs:30:18) + a :: a1 (bound at T13784.hs:30:13) + divide :: Product (a : as) -> (b, Product (Divide b (a : as))) + (bound at T13784.hs:30:5) + +T13784.hs:30:29: error: + • Couldn't match expected type ‘Product as0’ + with actual type ‘(a0, Product (Divide a0 as1))’ + • In the second argument of ‘(:*)’, namely ‘divide as’ + In the expression: a :* divide as + In an equation for ‘divide’: divide (a :* as) = a :* divide as + • Relevant bindings include + as :: Product as1 (bound at T13784.hs:30:18) diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index 24abd30..50257e6 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -134,3 +134,4 @@ test('T7102', [ expect_broken(7102) ], ghci_script, ['T7102.script']) test('T7102a', normal, ghci_script, ['T7102a.script']) test('T13271', normal, compile_fail, ['']) test('T13674', normal, compile_fail, ['']) +test('T13784', normal, compile_fail, ['']) From git at git.haskell.org Mon Jun 5 12:24:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jun 2017 12:24:24 +0000 (UTC) Subject: [commit: ghc] master: Make the MR warning more accurage (a65dfea) Message-ID: <20170605122424.5A8C53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a65dfea535ddf3ca6aa2380ad38cb60cf5c0f1d8/ghc >--------------------------------------------------------------- commit a65dfea535ddf3ca6aa2380ad38cb60cf5c0f1d8 Author: Simon Peyton Jones Date: Mon Jun 5 11:16:16 2017 +0100 Make the MR warning more accurage Trac #13785 showed that we were emitting monomorphism warnings when we shouldn't. The fix turned out to be simple. In fact test T10935 then turned out to be another example of the over-noisy warning so I changed the test slightly. >--------------------------------------------------------------- a65dfea535ddf3ca6aa2380ad38cb60cf5c0f1d8 compiler/typecheck/TcSimplify.hs | 22 +++++++++++++--------- testsuite/tests/typecheck/should_compile/T10935.hs | 2 +- .../tests/typecheck/should_compile/T10935.stderr | 6 +++--- testsuite/tests/typecheck/should_compile/T13785.hs | 16 ++++++++++++++++ .../tests/typecheck/should_compile/T13785.stderr | 12 ++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 6 files changed, 46 insertions(+), 13 deletions(-) diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index dcb146a..2e49f2a 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -818,16 +818,19 @@ decideMonoTyVars infer_mode name_taus psigs candidates ; gbl_tvs <- tcGetGlobalTyCoVars ; let eq_constraints = filter isEqPred candidates - constrained_tvs = tyCoVarsOfTypes no_quant - mono_tvs1 = growThetaTyVars eq_constraints $ - gbl_tvs `unionVarSet` constrained_tvs + mono_tvs1 = growThetaTyVars eq_constraints gbl_tvs + constrained_tvs = growThetaTyVars eq_constraints (tyCoVarsOfTypes no_quant) + `minusVarSet` mono_tvs1 + mono_tvs2 = mono_tvs1 `unionVarSet` constrained_tvs + -- A type variable is only "constrained" (so that the MR bites) + -- if it is not free in the environment (Trac #13785) -- Always quantify over partial-sig qtvs, so they are not mono -- Need to zonk them because they are meta-tyvar SigTvs -- Note [Quantification and partial signatures], wrinkle 3 ; psig_qtvs <- mapM zonkTcTyVarToTyVar $ concatMap (map snd . sig_inst_skols) psigs - ; let mono_tvs = mono_tvs1 `delVarSetList` psig_qtvs + ; let mono_tvs = mono_tvs2 `delVarSetList` psig_qtvs -- Warn about the monomorphism restriction ; warn_mono <- woptM Opt_WarnMonomorphism @@ -863,11 +866,12 @@ decideMonoTyVars infer_mode name_taus psigs candidates = False pp_bndrs = pprWithCommas (quotes . ppr . fst) name_taus - mr_msg = hang (text "The Monomorphism Restriction applies to the binding" - <> plural name_taus <+> text "for" <+> pp_bndrs) - 2 (text "Consider giving a type signature for" - <+> if isSingleton name_taus then pp_bndrs - else text "these binders") + mr_msg = hang (sep [ text "The Monomorphism Restriction applies to the binding" + <> plural name_taus + , text "for" <+> pp_bndrs ]) + 2 (hsep [ text "Consider giving" + , text (if isSingleton name_taus then "it" else "them") + , text "a type signature"]) ------------------- defaultTyVarsAndSimplify :: TcLevel diff --git a/testsuite/tests/typecheck/should_compile/T10935.hs b/testsuite/tests/typecheck/should_compile/T10935.hs index 9817ec8..7dde736 100644 --- a/testsuite/tests/typecheck/should_compile/T10935.hs +++ b/testsuite/tests/typecheck/should_compile/T10935.hs @@ -2,4 +2,4 @@ module T10935 where -f x = let y = x+1 in (y,y) +f x = let y = 1+1 in (y,y) diff --git a/testsuite/tests/typecheck/should_compile/T10935.stderr b/testsuite/tests/typecheck/should_compile/T10935.stderr index b8db0fb..31f1243 100644 --- a/testsuite/tests/typecheck/should_compile/T10935.stderr +++ b/testsuite/tests/typecheck/should_compile/T10935.stderr @@ -1,6 +1,6 @@ T10935.hs:5:11: warning: [-Wmonomorphism-restriction] • The Monomorphism Restriction applies to the binding for ‘y’ - Consider giving a type signature for ‘y’ - • In the expression: let y = x + 1 in (y, y) - In an equation for ‘f’: f x = let y = x + 1 in (y, y) + Consider giving it a type signature + • In the expression: let y = 1 + 1 in (y, y) + In an equation for ‘f’: f x = let y = 1 + 1 in (y, y) diff --git a/testsuite/tests/typecheck/should_compile/T13785.hs b/testsuite/tests/typecheck/should_compile/T13785.hs new file mode 100644 index 0000000..f02f04d --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13785.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE ScopedTypeVariables #-} +{-# OPTIONS_GHC -Wmonomorphism-restriction #-} +module Bug where + +class Monad m => C m where + c :: (m Char, m Char) + +foo :: forall m. C m => m Char +foo = bar >> baz >> bar2 + where + -- Should not get MR warning + bar, baz :: m Char + (bar, baz) = c + + -- Should get MR warning + (bar2, baz2) = c diff --git a/testsuite/tests/typecheck/should_compile/T13785.stderr b/testsuite/tests/typecheck/should_compile/T13785.stderr new file mode 100644 index 0000000..b86e7da --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13785.stderr @@ -0,0 +1,12 @@ + +T13785.hs:16:5: warning: [-Wmonomorphism-restriction] + • The Monomorphism Restriction applies to the bindings + for ‘bar2’, ‘baz2’ + Consider giving them a type signature + • In an equation for ‘foo’: + foo + = bar >> baz >> bar2 + where + bar, baz :: m Char + (bar, baz) = c + (bar2, baz2) = c diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 4bfaf90..c381fe1 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -561,3 +561,4 @@ 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('T13785', normal, compile, ['']) From git at git.haskell.org Mon Jun 5 17:15:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jun 2017 17:15:59 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Run stage1 tests as well (e898bcf) Message-ID: <20170605171559.4F15A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/e898bcfa01cd101b283773878339eaa51e782bed/ghc >--------------------------------------------------------------- commit e898bcfa01cd101b283773878339eaa51e782bed Author: Ben Gamari Date: Sun Jun 4 21:24:15 2017 -0400 Run stage1 tests as well >--------------------------------------------------------------- e898bcfa01cd101b283773878339eaa51e782bed 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 Mon Jun 5 17:16:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jun 2017 17:16:02 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Pass BINDIST to make test (c342afa) Message-ID: <20170605171602.163553A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c342afa42d108222e60f7cb7a8f787346300daa8/ghc >--------------------------------------------------------------- commit c342afa42d108222e60f7cb7a8f787346300daa8 Author: Ben Gamari Date: Mon Jun 5 13:15:45 2017 -0400 Pass BINDIST to make test >--------------------------------------------------------------- c342afa42d108222e60f7cb7a8f787346300daa8 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 Mon Jun 5 17:27:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jun 2017 17:27:39 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Use named argument list (339ba63) Message-ID: <20170605172739.AD5FD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/339ba637949c16f128735cfae42a025344119b93/ghc >--------------------------------------------------------------- commit 339ba637949c16f128735cfae42a025344119b93 Author: Ben Gamari Date: Mon Jun 5 13:27:27 2017 -0400 Use named argument list >--------------------------------------------------------------- 339ba637949c16f128735cfae42a025344119b93 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 Mon Jun 5 19:31:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jun 2017 19:31:45 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rework handling of nofib (24c4f9f) Message-ID: <20170605193145.6A7E43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/24c4f9f7fa82364fcd31447486a4edcfc18fc9eb/ghc >--------------------------------------------------------------- commit 24c4f9f7fa82364fcd31447486a4edcfc18fc9eb 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. >--------------------------------------------------------------- 24c4f9f7fa82364fcd31447486a4edcfc18fc9eb 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 Mon Jun 5 19:31:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jun 2017 19:31:48 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Don't try to record commit of bindist (fadc204) Message-ID: <20170605193148.43F723A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/fadc204d28157be69943f3e901500127fe866ce5/ghc >--------------------------------------------------------------- commit fadc204d28157be69943f3e901500127fe866ce5 Author: Ben Gamari Date: Mon Jun 5 15:31:26 2017 -0400 Don't try to record commit of bindist >--------------------------------------------------------------- fadc204d28157be69943f3e901500127fe866ce5 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 Mon Jun 5 20:09:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jun 2017 20:09:10 +0000 (UTC) Subject: [commit: ghc] master: Desugar modules compiled with -fno-code (c9eb438) Message-ID: <20170605200910.220AC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c9eb4385aad248118650725b7b699bb97ee21c0d/ghc >--------------------------------------------------------------- commit c9eb4385aad248118650725b7b699bb97ee21c0d Author: doug Date: Mon Jun 5 15:09:50 2017 -0400 Desugar modules compiled with -fno-code Previously modules with hscTarget == HscNothing were not desugared. This patch changes behavior so that all modules HsSrcFile Modules except GHC.Prim are desugared. Modules with hscTarget == HscNothing are not simplified. Warnings and errors produced by the desugarer will now be produced when compiling with -fno-code. HscMain.finishTypecheckingOnly is removed, HscMain.hscIncrementalCompile is simplified a bit, and HscMain.finish takes in the removed logic. I think this is easier to follow. Updates haddock submodule. Tests T8101, T8101b, T10600 are no longer expect_broken. Reviewers: ezyang, austin, bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #10600 Differential Revision: https://phabricator.haskell.org/D3542 >--------------------------------------------------------------- c9eb4385aad248118650725b7b699bb97ee21c0d compiler/main/HscMain.hs | 90 ++++++++++++++++++-------------------- testsuite/tests/driver/all.T | 6 +-- testsuite/tests/perf/haddock/all.T | 9 ++-- utils/haddock | 2 +- 4 files changed, 53 insertions(+), 54 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c9eb4385aad248118650725b7b699bb97ee21c0d From git at git.haskell.org Mon Jun 5 22:16:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jun 2017 22:16:42 +0000 (UTC) Subject: [commit: ghc] master: Udate hsSyn AST to use Trees that Grow (8e6ec0f) Message-ID: <20170605221642.878EE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8e6ec0fa7431b0454b09c0011a615f0845df1198/ghc >--------------------------------------------------------------- commit 8e6ec0fa7431b0454b09c0011a615f0845df1198 Author: Alan Zimmerman Date: Fri May 19 14:56:09 2017 +0200 Udate hsSyn AST to use Trees that Grow Summary: See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow This commit prepares the ground for a full extensible AST, by replacing the type parameter for the hsSyn data types with a set of indices into type families, data GhcPs -- ^ Index for GHC parser output data GhcRn -- ^ Index for GHC renamer output data GhcTc -- ^ Index for GHC typechecker output These are now used instead of `RdrName`, `Name` and `Id`/`TcId`/`Var` Where the original name type is required in a polymorphic context, this is accessible via the IdP type family, defined as type family IdP p type instance IdP GhcPs = RdrName type instance IdP GhcRn = Name type instance IdP GhcTc = Id These types are declared in the new 'hsSyn/HsExtension.hs' module. To gain a better understanding of the extension mechanism, it has been applied to `HsLit` only, also replacing the `SourceText` fields in them with extension types. To preserve extension generality, a type class is introduced to capture the `SourceText` interface, which must be honoured by all of the extension points which originally had a `SourceText`. The class is defined as class HasSourceText a where -- Provide setters to mimic existing constructors noSourceText :: a sourceText :: String -> a setSourceText :: SourceText -> a getSourceText :: a -> SourceText And the constraint is captured in `SourceTextX`, which is a constraint type listing all the extension points that make use of the class. Updating Haddock submodule to match. Test Plan: ./validate Reviewers: simonpj, shayan-najd, goldfire, austin, bgamari Subscribers: rwbarton, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D3609 >--------------------------------------------------------------- 8e6ec0fa7431b0454b09c0011a615f0845df1198 compiler/backpack/BkpSyn.hs | 3 +- compiler/backpack/DriverBkp.hs | 4 +- compiler/deSugar/Check.hs | 66 +-- compiler/deSugar/Coverage.hs | 122 ++--- compiler/deSugar/Desugar.hs | 7 +- compiler/deSugar/DsArrows.hs | 71 +-- compiler/deSugar/DsBinds.hs | 16 +- compiler/deSugar/DsExpr.hs | 41 +- compiler/deSugar/DsExpr.hs-boot | 16 +- compiler/deSugar/DsForeign.hs | 10 +- compiler/deSugar/DsGRHSs.hs | 18 +- compiler/deSugar/DsListComp.hs | 59 +-- compiler/deSugar/DsMeta.hs | 231 ++++----- compiler/deSugar/DsMonad.hs | 2 +- compiler/deSugar/DsUtils.hs | 29 +- compiler/deSugar/Match.hs | 43 +- compiler/deSugar/Match.hs-boot | 9 +- compiler/deSugar/MatchCon.hs | 8 +- compiler/deSugar/MatchLit.hs | 40 +- compiler/deSugar/PmExpr.hs | 12 +- compiler/ghc.cabal.in | 1 + compiler/ghc.mk | 1 + compiler/hsSyn/Convert.hs | 149 +++--- compiler/hsSyn/HsBinds.hs | 121 ++--- compiler/hsSyn/HsDecls.hs | 531 +++++++++++---------- compiler/hsSyn/HsDumpAst.hs | 28 +- compiler/hsSyn/HsExpr.hs | 461 +++++++++--------- compiler/hsSyn/HsExpr.hs-boot | 40 +- compiler/hsSyn/HsExtension.hs | 289 +++++++++++ compiler/hsSyn/HsImpExp.hs | 37 +- compiler/hsSyn/HsLit.hs | 132 +++-- compiler/hsSyn/HsPat.hs | 183 +++---- compiler/hsSyn/HsPat.hs-boot | 6 +- compiler/hsSyn/HsSyn.hs | 7 +- compiler/hsSyn/HsTypes.hs | 392 +++++++-------- compiler/hsSyn/HsUtils.hs | 297 ++++++------ compiler/hsSyn/PlaceHolder.hs | 50 -- compiler/main/GHC.hs | 8 +- compiler/main/HeaderInfo.hs | 7 +- compiler/main/Hooks.hs | 28 +- compiler/main/HscMain.hs | 16 +- compiler/main/HscStats.hs | 3 +- compiler/main/HscTypes.hs | 34 +- compiler/main/InteractiveEval.hs | 10 +- compiler/parser/Parser.y | 373 ++++++++------- compiler/parser/RdrHsSyn.hs | 245 +++++----- compiler/rename/RnBinds.hs | 150 +++--- compiler/rename/RnEnv.hs | 29 +- compiler/rename/RnExpr.hs | 226 ++++----- compiler/rename/RnExpr.hs-boot | 22 +- compiler/rename/RnFixity.hs | 2 +- compiler/rename/RnNames.hs | 87 ++-- compiler/rename/RnPat.hs | 64 +-- compiler/rename/RnSource.hs | 187 ++++---- compiler/rename/RnSplice.hs | 63 +-- compiler/rename/RnSplice.hs-boot | 12 +- compiler/rename/RnTypes.hs | 211 ++++---- compiler/rename/RnUtils.hs | 2 +- compiler/typecheck/Inst.hs | 29 +- compiler/typecheck/TcAnnotations.hs | 17 +- compiler/typecheck/TcArrows.hs | 19 +- compiler/typecheck/TcBackpack.hs | 1 + compiler/typecheck/TcBinds.hs | 96 ++-- compiler/typecheck/TcClassDcl.hs | 41 +- compiler/typecheck/TcDefaults.hs | 8 +- compiler/typecheck/TcDeriv.hs | 39 +- compiler/typecheck/TcDerivUtils.hs | 8 +- compiler/typecheck/TcEnv.hs | 18 +- compiler/typecheck/TcEnv.hs-boot | 1 + compiler/typecheck/TcExpr.hs | 146 +++--- compiler/typecheck/TcExpr.hs-boot | 31 +- compiler/typecheck/TcForeign.hs | 23 +- compiler/typecheck/TcGenDeriv.hs | 151 +++--- compiler/typecheck/TcGenFunctor.hs | 99 ++-- compiler/typecheck/TcGenGenerics.hs | 32 +- compiler/typecheck/TcHsSyn.hs | 137 +++--- compiler/typecheck/TcHsType.hs | 93 ++-- compiler/typecheck/TcInstDcls.hs | 72 +-- compiler/typecheck/TcInstDcls.hs-boot | 5 +- compiler/typecheck/TcMatches.hs | 106 ++-- compiler/typecheck/TcMatches.hs-boot | 11 +- compiler/typecheck/TcPat.hs | 53 +- compiler/typecheck/TcPatSyn.hs | 86 ++-- compiler/typecheck/TcPatSyn.hs-boot | 13 +- compiler/typecheck/TcRnDriver.hs | 63 +-- compiler/typecheck/TcRnExports.hs | 41 +- compiler/typecheck/TcRnTypes.hs | 73 +-- compiler/typecheck/TcRules.hs | 10 +- compiler/typecheck/TcSigs.hs | 34 +- compiler/typecheck/TcSimplify.hs | 16 +- compiler/typecheck/TcSplice.hs | 53 +- compiler/typecheck/TcSplice.hs-boot | 36 +- compiler/typecheck/TcTyClsDecls.hs | 112 ++--- compiler/typecheck/TcTyDecls.hs | 11 +- compiler/typecheck/TcTypeable.hs | 55 +-- compiler/typecheck/TcUnify.hs | 11 +- compiler/typecheck/TcUnify.hs-boot | 14 +- compiler/typecheck/TcValidity.hs | 2 +- docs/users_guide/8.4.1-notes.rst | 34 ++ ghc/GHCi/UI.hs | 6 +- ghc/GHCi/UI/Info.hs | 6 +- ghc/GHCi/UI/Monad.hs | 7 +- .../tests/ghc-api/annotations-literals/parsed.hs | 6 +- testsuite/tests/ghc-api/annotations/parseTree.hs | 2 +- .../tests/ghc-api/annotations/stringSource.hs | 6 +- testsuite/tests/ghc-api/annotations/t11430.hs | 4 +- .../tests/indexed-types/should_fail/T13784.hs | 6 +- .../tests/indexed-types/should_fail/T13784.stderr | 22 +- testsuite/tests/quasiquotation/T7918.hs | 6 +- utils/ghctags/Main.hs | 5 +- utils/haddock | 2 +- 111 files changed, 3941 insertions(+), 3348 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 8e6ec0fa7431b0454b09c0011a615f0845df1198 From git at git.haskell.org Tue Jun 6 12:33:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jun 2017 12:33:20 +0000 (UTC) Subject: [commit: ghc] master: Typo in output of remote slave startup [merge cand] (e77b9a2) Message-ID: <20170606123320.664C53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e77b9a2069bca9018f989d7c4f54da099e3ab215/ghc >--------------------------------------------------------------- commit e77b9a2069bca9018f989d7c4f54da099e3ab215 Author: Gabor Greif Date: Tue Jun 6 12:03:00 2017 +0200 Typo in output of remote slave startup [merge cand] The output is not being checked in the test suite. However other tools may check it for obtaining the status of the remote slave. So I'd suggest to merge this to 8.2 branch, in order to not fragment the tooling's checks. >--------------------------------------------------------------- e77b9a2069bca9018f989d7c4f54da099e3ab215 iserv/src/Remote/Slave.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/iserv/src/Remote/Slave.hs b/iserv/src/Remote/Slave.hs index c5b652d..b80d095 100644 --- a/iserv/src/Remote/Slave.hs +++ b/iserv/src/Remote/Slave.hs @@ -61,7 +61,7 @@ startSlave' verbose base_path port = do when verbose $ putStrLn "Opening socket" pipe <- acceptSocket sock >>= socketToPipe putStrLn $ "Listening on port " ++ show port - when verbose $ putStrLn "Staring serv" + when verbose $ putStrLn "Starting serv" uninterruptibleMask $ serv verbose (hook verbose base_path pipe) pipe when verbose $ putStrLn "serv ended" return () From git at git.haskell.org Wed Jun 7 12:47:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Jun 2017 12:47:44 +0000 (UTC) Subject: [commit: ghc] master: Spelling typos (92a4f90) Message-ID: <20170607124744.1E68D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/92a4f908f2599150bec0530d688997f03780646e/ghc >--------------------------------------------------------------- commit 92a4f908f2599150bec0530d688997f03780646e Author: Simon Peyton Jones Date: Wed Jun 7 08:58:52 2017 +0100 Spelling typos >--------------------------------------------------------------- 92a4f908f2599150bec0530d688997f03780646e compiler/typecheck/TcErrors.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index 4411d6a..ed1eb82 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -640,7 +640,7 @@ mkGivenErrorReporter implic ctxt cts ; err <- mkEqErr_help dflags ctxt report ct' Nothing ty1 ty2 - ; traceTc "mkGivenErrorRporter" (ppr ct) + ; traceTc "mkGivenErrorReporter" (ppr ct) ; maybeReportError ctxt err } where (ct : _ ) = cts -- Never empty @@ -648,9 +648,9 @@ mkGivenErrorReporter implic ctxt cts ignoreErrorReporter :: Reporter -- Discard Given errors that don't come from --- a pattern match; maybe we should warn instead?ignoreErrorReporter ctxt cts +-- a pattern match; maybe we should warn instead? ignoreErrorReporter ctxt cts - = do { traceTc "mkGivenErrorRporter no" (ppr cts $$ ppr (cec_encl ctxt)) + = do { traceTc "mkGivenErrorReporter no" (ppr cts $$ ppr (cec_encl ctxt)) ; return () } From git at git.haskell.org Wed Jun 7 12:47:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Jun 2017 12:47:48 +0000 (UTC) Subject: [commit: ghc] master: Stop the specialiser generating loopy code (2b74bd9) Message-ID: <20170607124748.9A1543A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2b74bd9d8b4c6b20f3e8d9ada12e7db645cc3c19/ghc >--------------------------------------------------------------- commit 2b74bd9d8b4c6b20f3e8d9ada12e7db645cc3c19 Author: Simon Peyton Jones Date: Wed Jun 7 12:03:51 2017 +0100 Stop the specialiser generating loopy code This patch fixes a bad bug in the specialiser, which showed up as Trac #13429. When specialising an imported DFun, the specialiser could generate a recusive loop where none existed in the original program. It's all rather tricky, and I've documented it at some length in Note [Avoiding loops] We'd encoutered exactly this before (Trac #3591) but I had failed to realise that the very same thing could happen for /imported/ DFuns. I did quite a bit of refactoring. The compiler seems to get a tiny bit faster on deriving/perf/T10858 but almost all the gain had occurred before now; this patch just pushed it over the line. >--------------------------------------------------------------- 2b74bd9d8b4c6b20f3e8d9ada12e7db645cc3c19 compiler/specialise/Specialise.hs | 413 ++++++++++++--------- testsuite/tests/deriving/perf/all.T | 4 +- testsuite/tests/simplCore/should_compile/T13429.hs | 114 ------ testsuite/tests/simplCore/should_compile/all.T | 1 - testsuite/tests/simplCore/should_run/T13429.hs | 63 ++++ .../tests/simplCore/should_run/T13429.stdout | 0 testsuite/tests/simplCore/should_run/T13429_2.hs | 10 + .../tests/simplCore/should_run/T13429_2.stdout | 1 + testsuite/tests/simplCore/should_run/T13429_2a.hs | 37 ++ testsuite/tests/simplCore/should_run/T13429a.hs | 343 +++++++++++++++++ testsuite/tests/simplCore/should_run/all.T | 2 + 11 files changed, 699 insertions(+), 289 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 2b74bd9d8b4c6b20f3e8d9ada12e7db645cc3c19 From git at git.haskell.org Wed Jun 7 14:16:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Jun 2017 14:16:00 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #13750 (ef07010) Message-ID: <20170607141600.A39193A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ef07010cf4f480d9f595a71cf5b009884522a75e/ghc >--------------------------------------------------------------- commit ef07010cf4f480d9f595a71cf5b009884522a75e Author: Simon Peyton Jones Date: Wed Jun 7 15:15:37 2017 +0100 Test Trac #13750 >--------------------------------------------------------------- ef07010cf4f480d9f595a71cf5b009884522a75e testsuite/tests/simplCore/should_run/T13750.hs | 47 +++++++++++++++++++ .../tests/simplCore/should_run/T13750.stdout | 0 testsuite/tests/simplCore/should_run/T13750a.hs | 54 ++++++++++++++++++++++ testsuite/tests/simplCore/should_run/all.T | 1 + 4 files changed, 102 insertions(+) diff --git a/testsuite/tests/simplCore/should_run/T13750.hs b/testsuite/tests/simplCore/should_run/T13750.hs new file mode 100644 index 0000000..7e3b9c0 --- /dev/null +++ b/testsuite/tests/simplCore/should_run/T13750.hs @@ -0,0 +1,47 @@ +{-# LANGUAGE ConstraintKinds #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE UndecidableSuperClasses #-} +{-# LANGUAGE PolyKinds #-} +module Main where + +import T13750a + +import GHC.Exts (Constraint) +import Unsafe.Coerce +import Data.Proxy + +class MyShow a where + myShow :: a -> String + +instance MyShow Char where + myShow a = [a] + +gshowS :: (All2 MyShow xss) => NS xss -> String +gshowS (Z xs) = gshowP xs +gshowS (S xss) = gshowS xss + +gshowP :: (All MyShow xs) => NP xs -> String +gshowP (x :* Nil) = myShow x + +class (AllF c xs) => All (c :: k -> Constraint) (xs :: [k]) + -- where foo :: Proxy c -- This makes it not seg-fault + +instance All c '[] +instance (c x, All c xs) => All c (x ': xs) + +type family AllF (c :: k -> Constraint) (xs :: [k]) :: Constraint +type instance AllF _c '[] = () +type instance AllF c (x ': xs) = (c x, All c xs) + +type All2 f = All (All f) + +main :: IO () +main = do + let t = 'x' :* Nil + print (gshowS (Z ('x' :* Nil) :: NS '[ '[ Char ] ])) diff --git a/libraries/base/tests/take001.stdout b/testsuite/tests/simplCore/should_run/T13750.stdout similarity index 100% copy from libraries/base/tests/take001.stdout copy to testsuite/tests/simplCore/should_run/T13750.stdout diff --git a/testsuite/tests/simplCore/should_run/T13750a.hs b/testsuite/tests/simplCore/should_run/T13750a.hs new file mode 100644 index 0000000..7ed72ca --- /dev/null +++ b/testsuite/tests/simplCore/should_run/T13750a.hs @@ -0,0 +1,54 @@ +{-# LANGUAGE GADTs #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE ViewPatterns #-} +module T13750a where + +import Unsafe.Coerce + +type family AnyT :: * where {} +type family AnyList :: [*] where {} + +newtype NP (xs :: [*]) = NP [AnyT] + +data IsNP (xs :: [*]) where + IsNil :: IsNP '[] + IsCons :: x -> NP xs -> IsNP (x ': xs) + +isNP :: NP xs -> IsNP xs +isNP (NP xs) = + if null xs + then unsafeCoerce IsNil + else unsafeCoerce (IsCons (head xs) (NP (tail xs))) + +pattern Nil :: () => (xs ~ '[]) => NP xs +pattern Nil <- (isNP -> IsNil) + where + Nil = NP [] + +pattern (:*) :: () => (xs' ~ (x ': xs)) => x -> NP xs -> NP xs' +pattern x :* xs <- (isNP -> IsCons x xs) + where + x :* NP xs = NP (unsafeCoerce x : xs) +infixr 5 :* + +data NS (xs :: [[*]]) = NS !Int (NP AnyList) + +data IsNS (xs :: [[*]]) where + IsZ :: NP x -> IsNS (x ': xs) + IsS :: NS xs -> IsNS (x ': xs) + +isNS :: NS xs -> IsNS xs +isNS (NS i x) + | i == 0 = unsafeCoerce (IsZ (unsafeCoerce x)) + | otherwise = unsafeCoerce (IsS (NS (i - 1) x)) + +pattern Z :: () => (xs' ~ (x ': xs)) => NP x -> NS xs' +pattern Z x <- (isNS -> IsZ x) + where + Z x = NS 0 (unsafeCoerce x) + +pattern S :: () => (xs' ~ (x ': xs)) => NS xs -> NS xs' +pattern S p <- (isNS -> IsS p) diff --git a/testsuite/tests/simplCore/should_run/all.T b/testsuite/tests/simplCore/should_run/all.T index bf9686e..75ff431 100644 --- a/testsuite/tests/simplCore/should_run/all.T +++ b/testsuite/tests/simplCore/should_run/all.T @@ -76,3 +76,4 @@ test('T13227', normal, compile_and_run, ['']) test('T13733', expect_broken(13733), compile_and_run, ['']) test('T13429', normal, compile_and_run, ['']) test('T13429_2', normal, compile_and_run, ['']) +test('T13750', normal, compile_and_run, ['']) From git at git.haskell.org Wed Jun 7 18:54:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Jun 2017 18:54:20 +0000 (UTC) Subject: [commit: nofib] master: Merge remote-tracking branch 'michalt/fibon' into HEAD (488a0d8) Message-ID: <20170607185420.0F8AF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/488a0d894af93140dea1d75718c4b44a2bb47c7e/nofib >--------------------------------------------------------------- commit 488a0d894af93140dea1d75718c4b44a2bb47c7e Merge: c6b9143 50812b1 Author: Ben Gamari Date: Wed Jun 7 14:53:53 2017 -0400 Merge remote-tracking branch 'michalt/fibon' into HEAD >--------------------------------------------------------------- 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 488a0d894af93140dea1d75718c4b44a2bb47c7e From git at git.haskell.org Wed Jun 7 18:54:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Jun 2017 18:54:17 +0000 (UTC) Subject: [commit: nofib] master: Remove fibon (50812b1) Message-ID: <20170607185417.687053A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/50812b141f1a6c372c85cceb3541e9c1c7bab926/nofib >--------------------------------------------------------------- commit 50812b141f1a6c372c85cceb3541e9c1c7bab926 Author: Michal Terepeta Date: Sun Feb 12 12:42:02 2017 +0100 Remove fibon Summary: It doesn't compile, nobody is running it and upstream seems to have abandoned it too. IMHO, at this point we should simply remove it and focus on improving the benchmarks that do work & adding new ones. See also the discussion in #11501 Signed-off-by: Michal Terepeta Test Plan: compile & run nofib Reviewers: bgamari Subscribers: >--------------------------------------------------------------- 50812b141f1a6c372c85cceb3541e9c1c7bab926 fibon/Hackage/Agum/Agum.stdout | 10 - fibon/Hackage/Agum/ChangeLog | 36 - fibon/Hackage/Agum/Makefile | 8 - fibon/Hackage/Agum/eqn.txt | 2 - fibon/Hackage/Agum/license.txt | 675 - fibon/Hackage/Agum/readme.txt | 21 - .../Agum/src/Algebra/AbelianGroup/IntLinEq.hs | 206 - .../Hackage/Agum/src/Algebra/AbelianGroup/Main.hs | 111 - .../Algebra/AbelianGroup/UnificationMatching.hs | 407 - fibon/Hackage/Bzlib/Bzlib.stdout | 1 - fibon/Hackage/Bzlib/Codec/Compression/BZip.hs | 112 - .../Bzlib/Codec/Compression/BZip/Internal.hs | 290 - .../Bzlib/Codec/Compression/BZip/Stream.hsc | 599 - fibon/Hackage/Bzlib/LICENSE | 23 - fibon/Hackage/Bzlib/Main.hs | 16 - fibon/Hackage/Bzlib/Makefile | 13 - fibon/Hackage/Bzlib/bunzip2.hs | 6 - fibon/Hackage/Bzlib/bzip2.hs | 6 - fibon/Hackage/Bzlib/cbits/blocksort.c | 1094 - fibon/Hackage/Bzlib/cbits/bzlib.c | 1572 - fibon/Hackage/Bzlib/cbits/bzlib.h | 282 - fibon/Hackage/Bzlib/cbits/bzlib_private.h | 509 - fibon/Hackage/Bzlib/cbits/compress.c | 672 - fibon/Hackage/Bzlib/cbits/crctable.c | 104 - fibon/Hackage/Bzlib/cbits/decompress.c | 626 - fibon/Hackage/Bzlib/cbits/huffman.c | 205 - fibon/Hackage/Bzlib/cbits/randtable.c | 84 - fibon/Hackage/Bzlib/mito.aa.bz2 | Bin 3246776 -> 0 bytes fibon/Hackage/Cpsa/ChangeLog | 1022 - fibon/Hackage/Cpsa/Cpsa.stderr | 1 - fibon/Hackage/Cpsa/Cpsa.stdout | 3866 - fibon/Hackage/Cpsa/Makefile | 23 - fibon/Hackage/Cpsa/NEWS | 457 - fibon/Hackage/Cpsa/README | 133 - fibon/Hackage/Cpsa/cpsatst | 15 - fibon/Hackage/Cpsa/doc/Make.hs | 315 - fibon/Hackage/Cpsa/doc/Makefile | 74 - fibon/Hackage/Cpsa/doc/README | 35 - fibon/Hackage/Cpsa/doc/SDAG.lhs | 317 - fibon/Hackage/Cpsa/doc/bcasyntax.tex | 82 - fibon/Hackage/Cpsa/doc/carriers.mp | 64 - fibon/Hackage/Cpsa/doc/cmstrands.mp | 24 - fibon/Hackage/Cpsa/doc/cpsa.bib | 170 - fibon/Hackage/Cpsa/doc/cpsa.mk | 38 - fibon/Hackage/Cpsa/doc/cpsadesign.pdf | Bin 198971 -> 0 bytes fibon/Hackage/Cpsa/doc/cpsadesign.tex | 1133 - fibon/Hackage/Cpsa/doc/cpsadiagrams.mp | 205 - fibon/Hackage/Cpsa/doc/cpsaoverview.pdf | Bin 78160 -> 0 bytes fibon/Hackage/Cpsa/doc/cpsaoverview.tex | 326 - fibon/Hackage/Cpsa/doc/cpsaprimer.pdf | Bin 190605 -> 0 bytes fibon/Hackage/Cpsa/doc/cpsaprimer.tex | 1151 - fibon/Hackage/Cpsa/doc/cpsaspec.pdf | Bin 349753 -> 0 bytes fibon/Hackage/Cpsa/doc/cpsaspec.tex | 2713 - fibon/Hackage/Cpsa/doc/cpsatheory.pdf | Bin 248116 -> 0 bytes fibon/Hackage/Cpsa/doc/cpsatheory.tex | 1351 - fibon/Hackage/Cpsa/doc/cpsauser.html | 505 - fibon/Hackage/Cpsa/doc/ffgg.scm | 23 - fibon/Hackage/Cpsa/doc/index.html | 52 - fibon/Hackage/Cpsa/doc/macros.tex | 60 - fibon/Hackage/Cpsa/doc/ns.scm | 35 - fibon/Hackage/Cpsa/doc/or.scm | 28 - fibon/Hackage/Cpsa/doc/strands.mp | 91 - fibon/Hackage/Cpsa/doc/termtree.mp | 60 - fibon/Hackage/Cpsa/doc/woolam.scm | 26 - fibon/Hackage/Cpsa/doc/yahalom.scm | 34 - fibon/Hackage/Cpsa/generated/Paths_cpsa.hs | 29 - fibon/Hackage/Cpsa/ghci | 2 - fibon/Hackage/Cpsa/license.txt | 38 - fibon/Hackage/Cpsa/nsl5.lisp | 147 - .../Cpsa/src/CPSA/Annotations/Annotations.hs | 518 - .../Hackage/Cpsa/src/CPSA/Annotations/Formulas.hs | 329 - fibon/Hackage/Cpsa/src/CPSA/Annotations/Main.hs | 71 - fibon/Hackage/Cpsa/src/CPSA/Basic/Algebra.hs | 1097 - .../Hackage/Cpsa/src/CPSA/DiffieHellman/Algebra.hs | 1629 - .../Cpsa/src/CPSA/DiffieHellman/IntLinEq.hs | 197 - fibon/Hackage/Cpsa/src/CPSA/Graph/CompactView.hs | 100 - fibon/Hackage/Cpsa/src/CPSA/Graph/Config.hs | 27 - fibon/Hackage/Cpsa/src/CPSA/Graph/ExpandedView.hs | 172 - fibon/Hackage/Cpsa/src/CPSA/Graph/LaTeXView.hs | 148 - fibon/Hackage/Cpsa/src/CPSA/Graph/Layout.hs | 74 - fibon/Hackage/Cpsa/src/CPSA/Graph/Loader.hs | 433 - fibon/Hackage/Cpsa/src/CPSA/Graph/Main.hs | 155 - fibon/Hackage/Cpsa/src/CPSA/Graph/Preskeleton.hs | 104 - fibon/Hackage/Cpsa/src/CPSA/Graph/SVG.hs | 177 - fibon/Hackage/Cpsa/src/CPSA/Graph/Tree.hs | 201 - fibon/Hackage/Cpsa/src/CPSA/Graph/XMLOutput.hs | 88 - fibon/Hackage/Cpsa/src/CPSA/Lib/Algebra.hs | 185 - fibon/Hackage/Cpsa/src/CPSA/Lib/CPSA.hs | 32 - fibon/Hackage/Cpsa/src/CPSA/Lib/Cohort.hs | 555 - fibon/Hackage/Cpsa/src/CPSA/Lib/Displayer.hs | 173 - fibon/Hackage/Cpsa/src/CPSA/Lib/Entry.hs | 220 - fibon/Hackage/Cpsa/src/CPSA/Lib/Expand.hs | 108 - fibon/Hackage/Cpsa/src/CPSA/Lib/Loader.hs | 422 - fibon/Hackage/Cpsa/src/CPSA/Lib/Main.hs | 562 - fibon/Hackage/Cpsa/src/CPSA/Lib/Pretty.hs | 134 - fibon/Hackage/Cpsa/src/CPSA/Lib/Printer.hs | 60 - fibon/Hackage/Cpsa/src/CPSA/Lib/Protocol.hs | 224 - fibon/Hackage/Cpsa/src/CPSA/Lib/SExpr.hs | 278 - fibon/Hackage/Cpsa/src/CPSA/Lib/Strand.hs | 1653 - fibon/Hackage/Cpsa/src/CPSA/Lib/Utilities.hs | 87 - fibon/Hackage/Cpsa/src/CPSA/Lib/Vector.hs | 55 - fibon/Hackage/Cpsa/src/CPSA/Parameters/Flow.hs | 90 - fibon/Hackage/Cpsa/src/CPSA/Parameters/Main.hs | 68 - fibon/Hackage/Cpsa/src/CPSA/Pretty/Main.hs | 42 - fibon/Hackage/Cpsa/src/CPSA/Shapes/Main.hs | 59 - fibon/Hackage/Cpsa/src/CPSA/Shapes/Shapes.hs | 107 - fibon/Hackage/Cpsa/src/cpsa.el | 159 - fibon/Hackage/Cpsa/src/cpsa.pl | 227 - fibon/Hackage/Cpsa/src/cpsa2svg | 296 - fibon/Hackage/Cpsa/src/cpsacgi | 17 - fibon/Hackage/Cpsa/src/cpsacgi.py | 222 - fibon/Hackage/Cpsa/src/cpsaops.scm | 102 - fibon/Hackage/Cpsa/src/httpd_allow_execmem.te | 23 - fibon/Hackage/Cpsa/src/index.html | 67 - fibon/Hackage/Cpsa/src/pp.pl | 176 - fibon/Hackage/Cpsa/src/preskel | 11 - fibon/Hackage/Cpsa/src/sexpr.pl | 361 - fibon/Hackage/Cpsa/tst/Make.hs | 315 - fibon/Hackage/Cpsa/tst/Makefile | 50 - fibon/Hackage/Cpsa/tst/README | 20 - fibon/Hackage/Cpsa/tst/blanchet.scm | 45 - fibon/Hackage/Cpsa/tst/blanchet.tst | 182 - fibon/Hackage/Cpsa/tst/checktst | 10 - fibon/Hackage/Cpsa/tst/completeness-test.scm | 56 - fibon/Hackage/Cpsa/tst/completeness-test.tst | 334 - fibon/Hackage/Cpsa/tst/cpsagraphall | 12 - fibon/Hackage/Cpsa/tst/cpsashapesall | 15 - fibon/Hackage/Cpsa/tst/dass-mod.lisp | 31 - fibon/Hackage/Cpsa/tst/dass.lisp | 31 - fibon/Hackage/Cpsa/tst/dass_simple.scm | 55 - fibon/Hackage/Cpsa/tst/dass_simple.tst | 330 - fibon/Hackage/Cpsa/tst/denning-sacco.scm | 25 - fibon/Hackage/Cpsa/tst/denning-sacco.tst | 399 - fibon/Hackage/Cpsa/tst/dh.sch | 26 - fibon/Hackage/Cpsa/tst/dh.tst | 384 - fibon/Hackage/Cpsa/tst/dh_unifywithconst.sch | 25 - fibon/Hackage/Cpsa/tst/dh_unifywithconst.tst | 59 - fibon/Hackage/Cpsa/tst/ds-short.lisp | 33 - fibon/Hackage/Cpsa/tst/dy.lsp | 35 - fibon/Hackage/Cpsa/tst/dy.tst | 1334 - fibon/Hackage/Cpsa/tst/encsig.scm | 41 - fibon/Hackage/Cpsa/tst/encsig.tst | 378 - fibon/Hackage/Cpsa/tst/epmo.scm | 80 - fibon/Hackage/Cpsa/tst/epmo.tst | 618 - fibon/Hackage/Cpsa/tst/epmo_acctnum.lsp | 99 - fibon/Hackage/Cpsa/tst/epmo_acctnum.tst | 1620 - fibon/Hackage/Cpsa/tst/ffgg.scm | 23 - fibon/Hackage/Cpsa/tst/ffgg.tst | 117 - fibon/Hackage/Cpsa/tst/isoreject.scm | 22 - fibon/Hackage/Cpsa/tst/isoreject.tst | 143 - fibon/Hackage/Cpsa/tst/kelly1.scm | 84 - fibon/Hackage/Cpsa/tst/kelly1.tst | 147 - fibon/Hackage/Cpsa/tst/kelly64.lisp | 127 - fibon/Hackage/Cpsa/tst/kerb5.lisp | 94 - fibon/Hackage/Cpsa/tst/kerberos.scm | 37 - fibon/Hackage/Cpsa/tst/kerberos.tst | 862 - fibon/Hackage/Cpsa/tst/missing_contraction.scm | 34 - fibon/Hackage/Cpsa/tst/missing_contraction.tst | 209 - fibon/Hackage/Cpsa/tst/neuman-stubblebine-alt.lisp | 36 - .../Cpsa/tst/neuman-stubblebine-reauth.lisp | 42 - .../Hackage/Cpsa/tst/neuman-stubblebine-reauth.lsp | 38 - .../Hackage/Cpsa/tst/neuman-stubblebine-reauth.tst | 3812 - fibon/Hackage/Cpsa/tst/neuman-stubblebine.scm | 37 - fibon/Hackage/Cpsa/tst/neuman-stubblebine.tst | 350 - fibon/Hackage/Cpsa/tst/no_contraction.scm | 16 - fibon/Hackage/Cpsa/tst/no_contraction.tst | 53 - fibon/Hackage/Cpsa/tst/non_transforming.scm | 33 - fibon/Hackage/Cpsa/tst/non_transforming.tst | 229 - fibon/Hackage/Cpsa/tst/ns.scm | 104 - fibon/Hackage/Cpsa/tst/ns.tst | 376 - fibon/Hackage/Cpsa/tst/nsl3.scm | 53 - fibon/Hackage/Cpsa/tst/nsl3.tst | 779 - fibon/Hackage/Cpsa/tst/nsl4.lisp | 85 - fibon/Hackage/Cpsa/tst/nsl4cm1.lsp | 47 - fibon/Hackage/Cpsa/tst/nsl4cm1.tst | 624 - fibon/Hackage/Cpsa/tst/nsl4resp2.lisp | 73 - fibon/Hackage/Cpsa/tst/nsl5.lisp | 147 - fibon/Hackage/Cpsa/tst/nsl5i.lisp | 64 - fibon/Hackage/Cpsa/tst/nslsk.scm | 51 - fibon/Hackage/Cpsa/tst/nslsk.tst | 240 - fibon/Hackage/Cpsa/tst/or.scm | 28 - fibon/Hackage/Cpsa/tst/or.tst | 228 - fibon/Hackage/Cpsa/tst/pca.lsp | 33 - fibon/Hackage/Cpsa/tst/pca.tst | 271 - fibon/Hackage/Cpsa/tst/pruning1.scm | 32 - fibon/Hackage/Cpsa/tst/pruning1.tst | 143 - fibon/Hackage/Cpsa/tst/sigenc.scm | 41 - fibon/Hackage/Cpsa/tst/sigenc.tst | 349 - fibon/Hackage/Cpsa/tst/sorted_epmo_acctnum.scm | 84 - fibon/Hackage/Cpsa/tst/sorted_epmo_acctnum.tst | 1624 - fibon/Hackage/Cpsa/tst/targetterms2.scm | 23 - fibon/Hackage/Cpsa/tst/targetterms2.tst | 195 - fibon/Hackage/Cpsa/tst/targetterms6.scm | 32 - fibon/Hackage/Cpsa/tst/targetterms6.tst | 206 - fibon/Hackage/Cpsa/tst/tnsl5.lisp | 168 - fibon/Hackage/Cpsa/tst/uncarried_keys.scm | 19 - fibon/Hackage/Cpsa/tst/uncarried_keys.tst | 125 - fibon/Hackage/Cpsa/tst/uo.scm | 15 - fibon/Hackage/Cpsa/tst/uo.tst | 29 - fibon/Hackage/Cpsa/tst/updatetst | 19 - fibon/Hackage/Cpsa/tst/weird.scm | 24 - fibon/Hackage/Cpsa/tst/weird.tst | 77 - fibon/Hackage/Cpsa/tst/wmf.lsp | 26 - fibon/Hackage/Cpsa/tst/wmf.tst | 503 - fibon/Hackage/Cpsa/tst/woolam.scm | 26 - fibon/Hackage/Cpsa/tst/woolam.tst | 97 - fibon/Hackage/Cpsa/tst/yahalom.scm | 34 - fibon/Hackage/Cpsa/tst/yahalom.tst | 421 - fibon/Hackage/Crypto/Codec/Binary/BubbleBabble.hs | 41 - fibon/Hackage/Crypto/Codec/Encryption/AES.hs | 62 - fibon/Hackage/Crypto/Codec/Encryption/AESAux.hs | 1008 - fibon/Hackage/Crypto/Codec/Encryption/Blowfish.hs | 58 - .../Hackage/Crypto/Codec/Encryption/BlowfishAux.hs | 282 - fibon/Hackage/Crypto/Codec/Encryption/DES.hs | 35 - fibon/Hackage/Crypto/Codec/Encryption/DESAux.hs | 179 - fibon/Hackage/Crypto/Codec/Encryption/Modes.hs | 61 - fibon/Hackage/Crypto/Codec/Encryption/Padding.hs | 108 - fibon/Hackage/Crypto/Codec/Encryption/RSA.hs | 79 - .../Hackage/Crypto/Codec/Encryption/RSA/EMEOAEP.hs | 95 - fibon/Hackage/Crypto/Codec/Encryption/RSA/MGF.hs | 32 - .../Crypto/Codec/Encryption/RSA/NumberTheory.hs | 203 - fibon/Hackage/Crypto/Codec/Encryption/TEA.hs | 85 - fibon/Hackage/Crypto/Codec/Text/Raw.hs | 49 - fibon/Hackage/Crypto/Codec/Utils.hs | 138 - fibon/Hackage/Crypto/Crypto.stdout | 4 - fibon/Hackage/Crypto/CryptoHomePage.html | 51 - fibon/Hackage/Crypto/Data/Digest/MD5.hs | 41 - fibon/Hackage/Crypto/Data/Digest/MD5Aux.hs | 355 - fibon/Hackage/Crypto/Data/Digest/SHA1.hs | 120 - fibon/Hackage/Crypto/Data/Digest/SHA2.hs | 285 - fibon/Hackage/Crypto/Data/Digest/SHA224.hs | 26 - fibon/Hackage/Crypto/Data/Digest/SHA256.hs | 26 - fibon/Hackage/Crypto/Data/Digest/SHA384.hs | 26 - fibon/Hackage/Crypto/Data/Digest/SHA512.hs | 26 - fibon/Hackage/Crypto/Data/HMAC.hs | 118 - fibon/Hackage/Crypto/Data/LargeWord.hs | 147 - fibon/Hackage/Crypto/HMACTest.hs | 183 - fibon/Hackage/Crypto/Main.hs | 72 - fibon/Hackage/Crypto/Makefile | 24 - fibon/Hackage/Crypto/QuickTest.hs | 74 - fibon/Hackage/Crypto/RSATest.hs | 139 - fibon/Hackage/Crypto/ReadMe.tex | 374 - fibon/Hackage/Crypto/SHA1Test.hs | 35 - fibon/Hackage/Crypto/SymmetricTest.hs | 232 - fibon/Hackage/Crypto/WordListTest.hs | 67 - fibon/Hackage/Crypto/plain.txt | 1000 - fibon/Hackage/Fgl/Data/Graph/Inductive.hs | 33 - fibon/Hackage/Fgl/Data/Graph/Inductive/Basic.hs | 126 - fibon/Hackage/Fgl/Data/Graph/Inductive/Example.hs | 187 - fibon/Hackage/Fgl/Data/Graph/Inductive/Graph.hs | 458 - fibon/Hackage/Fgl/Data/Graph/Inductive/Graphviz.hs | 70 - .../Fgl/Data/Graph/Inductive/Internal/FiniteMap.hs | 209 - .../Fgl/Data/Graph/Inductive/Internal/Heap.hs | 91 - .../Fgl/Data/Graph/Inductive/Internal/Queue.hs | 26 - .../Fgl/Data/Graph/Inductive/Internal/RootPath.hs | 51 - .../Fgl/Data/Graph/Inductive/Internal/Thread.hs | 149 - fibon/Hackage/Fgl/Data/Graph/Inductive/Monad.hs | 227 - .../Fgl/Data/Graph/Inductive/Monad/IOArray.hs | 112 - fibon/Hackage/Fgl/Data/Graph/Inductive/NodeMap.hs | 248 - .../Fgl/Data/Graph/Inductive/PatriciaTree.hs | 206 - fibon/Hackage/Fgl/Data/Graph/Inductive/Query.hs | 29 - .../Fgl/Data/Graph/Inductive/Query/ArtPoint.hs | 122 - .../Hackage/Fgl/Data/Graph/Inductive/Query/BCC.hs | 76 - .../Hackage/Fgl/Data/Graph/Inductive/Query/BFS.hs | 131 - .../Hackage/Fgl/Data/Graph/Inductive/Query/DFS.hs | 223 - .../Fgl/Data/Graph/Inductive/Query/Dominators.hs | 120 - .../Hackage/Fgl/Data/Graph/Inductive/Query/GVD.hs | 51 - .../Fgl/Data/Graph/Inductive/Query/Indep.hs | 24 - .../Hackage/Fgl/Data/Graph/Inductive/Query/MST.hs | 41 - .../Fgl/Data/Graph/Inductive/Query/MaxFlow.hs | 127 - .../Fgl/Data/Graph/Inductive/Query/MaxFlow2.hs | 263 - .../Fgl/Data/Graph/Inductive/Query/Monad.hs | 227 - fibon/Hackage/Fgl/Data/Graph/Inductive/Query/SP.hs | 32 - .../Fgl/Data/Graph/Inductive/Query/TransClos.hs | 21 - fibon/Hackage/Fgl/Data/Graph/Inductive/Tree.hs | 99 - fibon/Hackage/Fgl/Fgl.stdout | 24 - fibon/Hackage/Fgl/LICENSE | 29 - fibon/Hackage/Fgl/Main.hs | 49 - fibon/Hackage/Fgl/Makefile | 14 - fibon/Hackage/Fgl/graphs/anna.col | 990 - fibon/Hackage/Fgl/graphs/david.col | 816 - fibon/Hackage/Fgl/graphs/fpsol2.i.1.col | 11663 - fibon/Hackage/Fgl/graphs/fpsol2.i.2.col | 8700 - fibon/Hackage/Fgl/graphs/fpsol2.i.3.col | 8697 - fibon/Hackage/Fgl/graphs/games120.col | 1280 - fibon/Hackage/Fgl/graphs/homer.col | 3262 - fibon/Hackage/Fgl/graphs/huck.col | 606 - fibon/Hackage/Fgl/graphs/inithx.i.1.col | 18716 - fibon/Hackage/Fgl/graphs/inithx.i.2.col | 13988 - fibon/Hackage/Fgl/graphs/inithx.i.3.col | 13978 - fibon/Hackage/Fgl/graphs/jean.col | 512 - fibon/Hackage/Fgl/graphs/le450_15a.col | 8202 - fibon/Hackage/Fgl/graphs/le450_15b.col | 8203 - fibon/Hackage/Fgl/graphs/le450_15c.col | 16714 - fibon/Hackage/Fgl/graphs/le450_15d.col | 16784 - fibon/Hackage/Fgl/graphs/le450_25a.col | 8294 - fibon/Hackage/Fgl/graphs/le450_25b.col | 8297 - fibon/Hackage/Fgl/graphs/le450_25c.col | 17377 - fibon/Hackage/Fgl/graphs/le450_25d.col | 17459 - fibon/Hackage/Fgl/graphs/le450_5a.col | 5748 - fibon/Hackage/Fgl/graphs/le450_5b.col | 5768 - fibon/Hackage/Fgl/graphs/le450_5c.col | 9837 - fibon/Hackage/Fgl/graphs/le450_5d.col | 9791 - fibon/Hackage/Fgl/graphs/miles1000.col | 6436 - fibon/Hackage/Fgl/graphs/miles1500.col | 10400 - fibon/Hackage/Fgl/graphs/miles250.col | 778 - fibon/Hackage/Fgl/graphs/miles500.col | 2344 - fibon/Hackage/Fgl/graphs/miles750.col | 4230 - fibon/Hackage/Fgl/graphs/mulsol.i.1.col | 3934 - fibon/Hackage/Fgl/graphs/mulsol.i.2.col | 3894 - fibon/Hackage/Fgl/graphs/mulsol.i.3.col | 3925 - fibon/Hackage/Fgl/graphs/mulsol.i.4.col | 3955 - fibon/Hackage/Fgl/graphs/mulsol.i.5.col | 3982 - fibon/Hackage/Fgl/graphs/myciel3.col | 26 - fibon/Hackage/Fgl/graphs/myciel4.col | 77 - fibon/Hackage/Fgl/graphs/myciel5.col | 242 - fibon/Hackage/Fgl/graphs/myciel6.col | 761 - fibon/Hackage/Fgl/graphs/myciel7.col | 2366 - fibon/Hackage/Fgl/graphs/queen10_10.col | 2944 - fibon/Hackage/Fgl/graphs/queen11_11.col | 3964 - fibon/Hackage/Fgl/graphs/queen12_12.col | 5196 - fibon/Hackage/Fgl/graphs/queen13_13.col | 6660 - fibon/Hackage/Fgl/graphs/queen14_14.col | 8376 - fibon/Hackage/Fgl/graphs/queen15_15.col | 10364 - fibon/Hackage/Fgl/graphs/queen16_16.col | 12644 - fibon/Hackage/Fgl/graphs/queen5_5.col | 324 - fibon/Hackage/Fgl/graphs/queen6_6.col | 584 - fibon/Hackage/Fgl/graphs/queen7_7.col | 956 - fibon/Hackage/Fgl/graphs/queen8_12.col | 2740 - fibon/Hackage/Fgl/graphs/queen8_8.col | 1460 - fibon/Hackage/Fgl/graphs/queen9_9.col | 2116 - fibon/Hackage/Fgl/graphs/school1.col | 19102 - fibon/Hackage/Fgl/graphs/school1_nsh.col | 14619 - fibon/Hackage/Fgl/graphs/zeroin.i.1.col | 4109 - fibon/Hackage/Fgl/graphs/zeroin.i.2.col | 3550 - fibon/Hackage/Fgl/graphs/zeroin.i.3.col | 3549 - fibon/Hackage/Fgl/le450_15a.col | 8202 - fibon/Hackage/Fgl/le450_15b.col | 8203 - fibon/Hackage/Fgl/le450_15c.col | 16714 - fibon/Hackage/Fgl/le450_15d.col | 16784 - fibon/Hackage/Fgl/le450_25a.col | 8294 - fibon/Hackage/Fgl/le450_25b.col | 8297 - fibon/Hackage/Fgl/le450_25c.col | 17377 - fibon/Hackage/Fgl/le450_25d.col | 17459 - fibon/Hackage/Fgl/le450_5a.col | 5748 - fibon/Hackage/Fgl/le450_5b.col | 5768 - fibon/Hackage/Fgl/le450_5c.col | 9837 - fibon/Hackage/Fgl/le450_5d.col | 9791 - fibon/Hackage/Fst/Fst.stdout | 1 - fibon/Hackage/Fst/LICENSE | 28 - fibon/Hackage/Fst/Makefile | 36 - fibon/Hackage/Fst/PLONK | 1 - fibon/Hackage/Fst/soda.fst | 7 - fibon/Hackage/Fst/src/FST/Alex.hs | 377 - fibon/Hackage/Fst/src/FST/Arguments.hs | 180 - fibon/Hackage/Fst/src/FST/Automaton.hs | 96 - fibon/Hackage/Fst/src/FST/AutomatonInterface.hs | 58 - fibon/Hackage/Fst/src/FST/AutomatonTypes.hs | 63 - fibon/Hackage/Fst/src/FST/Complete.hs | 28 - fibon/Hackage/Fst/src/FST/Deterministic.hs | 73 - fibon/Hackage/Fst/src/FST/DeterministicT.hs | 75 - fibon/Hackage/Fst/src/FST/EpsilonFreeT.hs | 46 - fibon/Hackage/Fst/src/FST/FileImport.hs | 24 - fibon/Hackage/Fst/src/FST/GetOpt.hs | 154 - fibon/Hackage/Fst/src/FST/Info.hs | 122 - fibon/Hackage/Fst/src/FST/LBFA.hs | 266 - fibon/Hackage/Fst/src/FST/LBFT.hs | 276 - fibon/Hackage/Fst/src/FST/Lexer.hs | 226 - fibon/Hackage/Fst/src/FST/Main.hs | 350 - fibon/Hackage/Fst/src/FST/MinimalBrzozowski.hs | 23 - fibon/Hackage/Fst/src/FST/MinimalTBrzozowski.hs | 23 - fibon/Hackage/Fst/src/FST/NReg.hs | 90 - fibon/Hackage/Fst/src/FST/Parse.hs | 981 - fibon/Hackage/Fst/src/FST/RRegTypes.hs | 113 - fibon/Hackage/Fst/src/FST/RegTypes.hs | 218 - fibon/Hackage/Fst/src/FST/Reversal.hs | 30 - fibon/Hackage/Fst/src/FST/ReversalT.hs | 30 - fibon/Hackage/Fst/src/FST/RunTransducer.hs | 66 - fibon/Hackage/Fst/src/FST/StateMonad.hs | 46 - fibon/Hackage/Fst/src/FST/Transducer.hs | 267 - fibon/Hackage/Fst/src/FST/TransducerInterface.hs | 88 - fibon/Hackage/Fst/src/FST/TransducerTypes.hs | 74 - fibon/Hackage/Fst/src/FST/Utils.hs | 64 - fibon/Hackage/Funsat/CHANGES | 15 - fibon/Hackage/Funsat/Funsat.stdout | 17 - fibon/Hackage/Funsat/LICENSE | 30 - fibon/Hackage/Funsat/Main.hs | 193 - fibon/Hackage/Funsat/Makefile | 42 - fibon/Hackage/Funsat/README | 39 - fibon/Hackage/Funsat/bimap/Data/Bimap.hs | 546 - fibon/Hackage/Funsat/bimap/HISTORY | 36 - fibon/Hackage/Funsat/bimap/LICENSE | 31 - fibon/Hackage/Funsat/bimap/Setup.lhs | 9 - fibon/Hackage/Funsat/bimap/Test/RunTests.hs | 13 - fibon/Hackage/Funsat/bimap/Test/Tests.hs | 444 - fibon/Hackage/Funsat/bimap/Test/Util.hs | 48 - fibon/Hackage/Funsat/bimap/bimap.cabal | 37 - fibon/Hackage/Funsat/bimap/tests.sh | 8 - fibon/Hackage/Funsat/bitset/Data/BitSet.hs | 116 - fibon/Hackage/Funsat/bitset/LICENSE | 165 - fibon/Hackage/Funsat/bitset/Setup.lhs | 4 - fibon/Hackage/Funsat/bitset/bitset.cabal | 20 - fibon/Hackage/Funsat/bitset/tests/Properties.hs | 81 - fibon/Hackage/Funsat/fgl/Data/Graph/Inductive.hs | 33 - .../Funsat/fgl/Data/Graph/Inductive/Basic.hs | 126 - .../Funsat/fgl/Data/Graph/Inductive/Example.hs | 187 - .../Funsat/fgl/Data/Graph/Inductive/Graph.hs | 458 - .../Funsat/fgl/Data/Graph/Inductive/Graphviz.hs | 70 - .../fgl/Data/Graph/Inductive/Internal/FiniteMap.hs | 209 - .../fgl/Data/Graph/Inductive/Internal/Heap.hs | 91 - .../fgl/Data/Graph/Inductive/Internal/Queue.hs | 26 - .../fgl/Data/Graph/Inductive/Internal/RootPath.hs | 51 - .../fgl/Data/Graph/Inductive/Internal/Thread.hs | 149 - .../Funsat/fgl/Data/Graph/Inductive/Monad.hs | 227 - .../fgl/Data/Graph/Inductive/Monad/IOArray.hs | 112 - .../Funsat/fgl/Data/Graph/Inductive/NodeMap.hs | 248 - .../fgl/Data/Graph/Inductive/PatriciaTree.hs | 206 - .../Funsat/fgl/Data/Graph/Inductive/Query.hs | 29 - .../fgl/Data/Graph/Inductive/Query/ArtPoint.hs | 122 - .../Funsat/fgl/Data/Graph/Inductive/Query/BCC.hs | 76 - .../Funsat/fgl/Data/Graph/Inductive/Query/BFS.hs | 131 - .../Funsat/fgl/Data/Graph/Inductive/Query/DFS.hs | 223 - .../fgl/Data/Graph/Inductive/Query/Dominators.hs | 120 - .../Funsat/fgl/Data/Graph/Inductive/Query/GVD.hs | 51 - .../Funsat/fgl/Data/Graph/Inductive/Query/Indep.hs | 24 - .../Funsat/fgl/Data/Graph/Inductive/Query/MST.hs | 41 - .../fgl/Data/Graph/Inductive/Query/MaxFlow.hs | 127 - .../fgl/Data/Graph/Inductive/Query/MaxFlow2.hs | 263 - .../Funsat/fgl/Data/Graph/Inductive/Query/Monad.hs | 227 - .../Funsat/fgl/Data/Graph/Inductive/Query/SP.hs | 32 - .../fgl/Data/Graph/Inductive/Query/TransClos.hs | 21 - .../Funsat/fgl/Data/Graph/Inductive/Tree.hs | 99 - fibon/Hackage/Funsat/fgl/LICENSE | 29 - fibon/Hackage/Funsat/fgl/Setup.hs | 6 - fibon/Hackage/Funsat/fgl/fgl.cabal | 42 - fibon/Hackage/Funsat/generated/Paths_funsat.hs | 29 - fibon/Hackage/Funsat/hole8.cnf | 310 - fibon/Hackage/Funsat/par16-5.cnf | 6738 - fibon/Hackage/Funsat/parse-dimacs/CHANGES | 17 - fibon/Hackage/Funsat/parse-dimacs/LICENSE | 165 - .../parse-dimacs/Language/CNF/Parse/ParseDIMACS.hs | 98 - fibon/Hackage/Funsat/parse-dimacs/Setup.hs | 2 - .../Hackage/Funsat/parse-dimacs/parse-dimacs.cabal | 40 - fibon/Hackage/Funsat/parsec/LICENSE | 21 - fibon/Hackage/Funsat/parsec/Setup.hs | 6 - fibon/Hackage/Funsat/parsec/Text/Parsec.hs | 36 - .../Funsat/parsec/Text/Parsec/ByteString.hs | 46 - .../Funsat/parsec/Text/Parsec/ByteString/Lazy.hs | 45 - fibon/Hackage/Funsat/parsec/Text/Parsec/Char.hs | 135 - .../Funsat/parsec/Text/Parsec/Combinator.hs | 286 - fibon/Hackage/Funsat/parsec/Text/Parsec/Error.hs | 197 - fibon/Hackage/Funsat/parsec/Text/Parsec/Expr.hs | 166 - .../Hackage/Funsat/parsec/Text/Parsec/Language.hs | 150 - fibon/Hackage/Funsat/parsec/Text/Parsec/Perm.hs | 181 - fibon/Hackage/Funsat/parsec/Text/Parsec/Pos.hs | 125 - fibon/Hackage/Funsat/parsec/Text/Parsec/Prim.hs | 725 - fibon/Hackage/Funsat/parsec/Text/Parsec/String.hs | 45 - fibon/Hackage/Funsat/parsec/Text/Parsec/Token.hs | 722 - .../Funsat/parsec/Text/ParserCombinators/Parsec.hs | 41 - .../parsec/Text/ParserCombinators/Parsec/Char.hs | 40 - .../Text/ParserCombinators/Parsec/Combinator.hs | 42 - .../parsec/Text/ParserCombinators/Parsec/Error.hs | 40 - .../parsec/Text/ParserCombinators/Parsec/Expr.hs | 42 - .../Text/ParserCombinators/Parsec/Language.hs | 28 - .../parsec/Text/ParserCombinators/Parsec/Perm.hs | 24 - .../parsec/Text/ParserCombinators/Parsec/Pos.hs | 35 - .../parsec/Text/ParserCombinators/Parsec/Prim.hs | 65 - .../parsec/Text/ParserCombinators/Parsec/Token.hs | 23 - fibon/Hackage/Funsat/parsec/parsec.cabal | 56 - fibon/Hackage/Funsat/src/Control/Monad/MonadST.hs | 42 - fibon/Hackage/Funsat/src/Funsat/Circuit.hs | 820 - fibon/Hackage/Funsat/src/Funsat/FastDom.hs | 122 - fibon/Hackage/Funsat/src/Funsat/Monad.hs | 94 - fibon/Hackage/Funsat/src/Funsat/Resolution.hs | 284 - fibon/Hackage/Funsat/src/Funsat/Solver.hs | 933 - fibon/Hackage/Funsat/src/Funsat/Types.hs | 328 - fibon/Hackage/Funsat/src/Funsat/Types/Internal.hs | 95 - fibon/Hackage/Funsat/src/Funsat/Utils.hs | 51 - fibon/Hackage/Funsat/src/Funsat/Utils/Internal.hs | 332 - fibon/Hackage/Funsat/src/Text/Tabular.hs | 70 - fibon/Hackage/Funsat/syb/LICENSE | 83 - fibon/Hackage/Funsat/syb/Setup.hs | 15 - fibon/Hackage/Funsat/syb/src/Data/Generics.hs | 42 - .../Funsat/syb/src/Data/Generics/Aliases.hs | 381 - .../Hackage/Funsat/syb/src/Data/Generics/Basics.hs | 26 - .../Funsat/syb/src/Data/Generics/Builders.hs | 65 - .../Funsat/syb/src/Data/Generics/Instances.hs | 193 - .../Funsat/syb/src/Data/Generics/Schemes.hs | 172 - fibon/Hackage/Funsat/syb/src/Data/Generics/Text.hs | 131 - .../Hackage/Funsat/syb/src/Data/Generics/Twins.hs | 272 - fibon/Hackage/Funsat/syb/src/Generics/SYB.hs | 17 - .../Hackage/Funsat/syb/src/Generics/SYB/Aliases.hs | 17 - .../Hackage/Funsat/syb/src/Generics/SYB/Basics.hs | 17 - .../Funsat/syb/src/Generics/SYB/Builders.hs | 17 - .../Funsat/syb/src/Generics/SYB/Instances.hs | 17 - .../Hackage/Funsat/syb/src/Generics/SYB/Schemes.hs | 17 - fibon/Hackage/Funsat/syb/src/Generics/SYB/Text.hs | 17 - fibon/Hackage/Funsat/syb/src/Generics/SYB/Twins.hs | 17 - fibon/Hackage/Funsat/syb/syb.cabal | 53 - fibon/Hackage/Funsat/syb/tests/Bits.hs | 214 - fibon/Hackage/Funsat/syb/tests/Builders.hs | 20 - fibon/Hackage/Funsat/syb/tests/CompanyDatatypes.hs | 39 - fibon/Hackage/Funsat/syb/tests/Datatype.hs | 35 - fibon/Hackage/Funsat/syb/tests/Encode.hs | 81 - fibon/Hackage/Funsat/syb/tests/Ext.hs | 30 - fibon/Hackage/Funsat/syb/tests/Ext1.hs | 124 - fibon/Hackage/Funsat/syb/tests/FoldTree.hs | 63 - fibon/Hackage/Funsat/syb/tests/FreeNames.hs | 120 - fibon/Hackage/Funsat/syb/tests/GEq.hs | 21 - fibon/Hackage/Funsat/syb/tests/GMapQAssoc.hs | 68 - fibon/Hackage/Funsat/syb/tests/GShow.hs | 52 - fibon/Hackage/Funsat/syb/tests/GShow2.hs | 47 - fibon/Hackage/Funsat/syb/tests/GZip.hs | 46 - fibon/Hackage/Funsat/syb/tests/GenUpTo.hs | 94 - fibon/Hackage/Funsat/syb/tests/GetC.hs | 121 - fibon/Hackage/Funsat/syb/tests/Gread.hs | 45 - fibon/Hackage/Funsat/syb/tests/Gread2.hs | 66 - fibon/Hackage/Funsat/syb/tests/HList.hs | 62 - fibon/Hackage/Funsat/syb/tests/HOPat.hs | 67 - fibon/Hackage/Funsat/syb/tests/Labels.hs | 30 - fibon/Hackage/Funsat/syb/tests/LocalQuantors.hs | 21 - fibon/Hackage/Funsat/syb/tests/Main.hs | 82 - fibon/Hackage/Funsat/syb/tests/NestedDatatypes.hs | 52 - fibon/Hackage/Funsat/syb/tests/Newtype.hs | 15 - fibon/Hackage/Funsat/syb/tests/Paradise.hs | 29 - fibon/Hackage/Funsat/syb/tests/Perm.hs | 127 - fibon/Hackage/Funsat/syb/tests/Polymatch.hs | 70 - fibon/Hackage/Funsat/syb/tests/Reify.hs | 413 - fibon/Hackage/Funsat/syb/tests/Strings.hs | 21 - fibon/Hackage/Funsat/syb/tests/Tree.hs | 62 - fibon/Hackage/Funsat/syb/tests/Twin.hs | 90 - fibon/Hackage/Funsat/syb/tests/Typeable.hs | 19 - fibon/Hackage/Funsat/syb/tests/Typecase1.hs | 59 - fibon/Hackage/Funsat/syb/tests/Typecase2.hs | 61 - fibon/Hackage/Funsat/syb/tests/Where.hs | 125 - fibon/Hackage/Funsat/syb/tests/XML.hs | 195 - fibon/Hackage/Gf/Adjective.gf | 35 - fibon/Hackage/Gf/AdjectiveEng.gf | 53 - fibon/Hackage/Gf/AdjectiveFre.gf | 2 - fibon/Hackage/Gf/AdjectiveRomance.gf | 59 - fibon/Hackage/Gf/Adverb.gf | 32 - fibon/Hackage/Gf/AdverbEng.gf | 20 - fibon/Hackage/Gf/AdverbFre.gf | 2 - fibon/Hackage/Gf/AdverbRomance.gf | 25 - fibon/Hackage/Gf/AllEng.gf | 9 - fibon/Hackage/Gf/AllEngAbs.gf | 9 - fibon/Hackage/Gf/AllFre.gf | 7 - fibon/Hackage/Gf/AllFreAbs.gf | 5 - fibon/Hackage/Gf/Backward.gf | 63 - fibon/Hackage/Gf/BackwardEng.gf | 76 - fibon/Hackage/Gf/BeschFre.gf | 102 - fibon/Hackage/Gf/Cat.gf | 133 - fibon/Hackage/Gf/CatEng.gf | 90 - fibon/Hackage/Gf/CatFre.gf | 5 - fibon/Hackage/Gf/CatRomance.gf | 112 - fibon/Hackage/Gf/Common.gf | 46 - fibon/Hackage/Gf/CommonRomance.gf | 250 - fibon/Hackage/Gf/CommonX.gf | 22 - fibon/Hackage/Gf/Compatibility.gf | 9 - fibon/Hackage/Gf/CompatibilityCat.gf | 11 - fibon/Hackage/Gf/CompatibilityEng.gf | 17 - fibon/Hackage/Gf/CompatibilityFre.gf | 11 - fibon/Hackage/Gf/Conjunction.gf | 45 - fibon/Hackage/Gf/ConjunctionEng.gf | 44 - fibon/Hackage/Gf/ConjunctionFre.gf | 2 - fibon/Hackage/Gf/ConjunctionRomance.gf | 52 - fibon/Hackage/Gf/ConstructX.gf | 19 - fibon/Hackage/Gf/Coordination.gf | 174 - fibon/Hackage/Gf/DictEng.gf | 43790 -- fibon/Hackage/Gf/DictEngAbs.gf | 43784 -- fibon/Hackage/Gf/DiffFre.gf | 227 - fibon/Hackage/Gf/DiffRomance.gf | 126 - fibon/Hackage/Gf/Eng.gf | 27 - fibon/Hackage/Gf/EngDescr.gf | 23 - fibon/Hackage/Gf/EngReal.gf | 31 - fibon/Hackage/Gf/ExtRomance.gf | 14 - fibon/Hackage/Gf/Extra.gf | 46 - fibon/Hackage/Gf/ExtraEng.gf | 100 - fibon/Hackage/Gf/ExtraEngAbs.gf | 19 - fibon/Hackage/Gf/ExtraFre.gf | 60 - fibon/Hackage/Gf/ExtraFreAbs.gf | 34 - fibon/Hackage/Gf/ExtraRomance.gf | 34 - fibon/Hackage/Gf/ExtraRomanceAbs.gf | 8 - fibon/Hackage/Gf/ExtraRomanceFre.gf | 2 - fibon/Hackage/Gf/Formal.gf | 53 - fibon/Hackage/Gf/Fre.gf | 38 - fibon/Hackage/Gf/Fre.hs.expected | 1380 - fibon/Hackage/Gf/FreDescr.gf | 44 - fibon/Hackage/Gf/FreReal.gf | 71 - fibon/Hackage/Gf/Grammar.gf | 23 - fibon/Hackage/Gf/GrammarEng.gf | 22 - fibon/Hackage/Gf/GrammarFre.gf | 22 - fibon/Hackage/Gf/HTML.gf | 8 - fibon/Hackage/Gf/Idiom.gf | 23 - fibon/Hackage/Gf/IdiomEng.gf | 32 - fibon/Hackage/Gf/IdiomFre.gf | 50 - fibon/Hackage/Gf/IrregEng.gf | 181 - fibon/Hackage/Gf/IrregEngAbs.gf | 176 - fibon/Hackage/Gf/IrregFre.gf | 395 - fibon/Hackage/Gf/IrregFreAbs.gf | 391 - fibon/Hackage/Gf/LICENSE | 340 - fibon/Hackage/Gf/Lang.gf | 13 - fibon/Hackage/Gf/LangEng.gf | 10 - fibon/Hackage/Gf/LangFre.gf | 10 - fibon/Hackage/Gf/Latex.gf | 12 - fibon/Hackage/Gf/Lexicon.gf | 350 - fibon/Hackage/Gf/LexiconEng.gf | 375 - fibon/Hackage/Gf/LexiconFre.gf | 367 - fibon/Hackage/Gf/MakeStructuralEng.gf | 13 - fibon/Hackage/Gf/MakeStructuralFre.gf | 23 - fibon/Hackage/Gf/Makefile | 153 - fibon/Hackage/Gf/MorphoEng.gf | 40 - fibon/Hackage/Gf/MorphoFre.gf | 1242 - fibon/Hackage/Gf/Noun.gf | 136 - fibon/Hackage/Gf/NounEng.gf | 138 - fibon/Hackage/Gf/NounFre.gf | 4 - fibon/Hackage/Gf/NounRomance.gf | 163 - fibon/Hackage/Gf/Numeral.gf | 60 - fibon/Hackage/Gf/NumeralEng.gf | 95 - fibon/Hackage/Gf/NumeralFre.gf | 180 - fibon/Hackage/Gf/NumeralTransfer.gf | 92 - fibon/Hackage/Gf/Overload.gf | 101 - fibon/Hackage/Gf/OverloadEng.gf | 1 - fibon/Hackage/Gf/ParadigmsEng.gf | 701 - fibon/Hackage/Gf/ParadigmsFre.gf | 446 - fibon/Hackage/Gf/ParamX.gf | 65 - fibon/Hackage/Gf/PhonoFre.gf | 28 - fibon/Hackage/Gf/Phrase.gf | 47 - fibon/Hackage/Gf/PhraseEng.gf | 27 - fibon/Hackage/Gf/PhraseFre.gf | 2 - fibon/Hackage/Gf/PhraseRomance.gf | 30 - fibon/Hackage/Gf/Precedence.gf | 117 - fibon/Hackage/Gf/Predef.gf | 37 - fibon/Hackage/Gf/PredefAbs.gf | 4 - fibon/Hackage/Gf/PredefCnc.gf | 4 - fibon/Hackage/Gf/Prelude.gf | 142 - fibon/Hackage/Gf/Question.gf | 41 - fibon/Hackage/Gf/QuestionEng.gf | 55 - fibon/Hackage/Gf/QuestionFre.gf | 2 - fibon/Hackage/Gf/QuestionRomance.gf | 113 - fibon/Hackage/Gf/README | 33 - fibon/Hackage/Gf/Relative.gf | 26 - fibon/Hackage/Gf/RelativeEng.gf | 52 - fibon/Hackage/Gf/RelativeFre.gf | 2 - fibon/Hackage/Gf/RelativeRomance.gf | 50 - fibon/Hackage/Gf/ResEng.gf | 474 - fibon/Hackage/Gf/ResFre.gf | 13 - fibon/Hackage/Gf/ResRomance.gf | 274 - fibon/Hackage/Gf/Sentence.gf | 104 - fibon/Hackage/Gf/SentenceEng.gf | 69 - fibon/Hackage/Gf/SentenceFre.gf | 2 - fibon/Hackage/Gf/SentenceRomance.gf | 78 - fibon/Hackage/Gf/Structural.gf | 128 - fibon/Hackage/Gf/StructuralEng.gf | 144 - fibon/Hackage/Gf/StructuralFre.gf | 207 - fibon/Hackage/Gf/Symbol.gf | 46 - fibon/Hackage/Gf/SymbolEng.gf | 44 - fibon/Hackage/Gf/SymbolFre.gf | 4 - fibon/Hackage/Gf/SymbolRomance.gf | 41 - fibon/Hackage/Gf/Tense.gf | 22 - fibon/Hackage/Gf/TenseFre.gf | 3 - fibon/Hackage/Gf/TenseRomance.gf | 12 - fibon/Hackage/Gf/TenseX.gf | 14 - fibon/Hackage/Gf/Text.gf | 15 - fibon/Hackage/Gf/TextX.gf | 11 - fibon/Hackage/Gf/Verb.gf | 71 - fibon/Hackage/Gf/VerbEng.gf | 50 - fibon/Hackage/Gf/VerbFre.gf | 4 - fibon/Hackage/Gf/VerbRomance.gf | 120 - fibon/Hackage/Gf/generated/Paths_gf.hs | 29 - fibon/Hackage/Gf/src/compiler/GF.hs | 49 - .../Hackage/Gf/src/compiler/GF/Command/Abstract.hs | 79 - .../Hackage/Gf/src/compiler/GF/Command/Commands.hs | 1091 - .../Gf/src/compiler/GF/Command/Importing.hs | 50 - .../Gf/src/compiler/GF/Command/Interpreter.hs | 132 - .../Hackage/Gf/src/compiler/GF/Command/Messages.hs | 54 - fibon/Hackage/Gf/src/compiler/GF/Command/Parse.hs | 64 - .../Gf/src/compiler/GF/Command/TreeOperations.hs | 32 - fibon/Hackage/Gf/src/compiler/GF/Compile.hs | 235 - .../Gf/src/compiler/GF/Compile/Abstract/Compute.hs | 138 - .../Gf/src/compiler/GF/Compile/Abstract/TC.hs | 297 - .../src/compiler/GF/Compile/Abstract/TypeCheck.hs | 82 - .../Gf/src/compiler/GF/Compile/CheckGrammar.hs | 291 - fibon/Hackage/Gf/src/compiler/GF/Compile/Coding.hs | 59 - .../compiler/GF/Compile/Concrete/AppPredefined.hs | 158 - .../Gf/src/compiler/GF/Compile/Concrete/Compute.hs | 456 - .../src/compiler/GF/Compile/Concrete/TypeCheck.hs | 692 - .../Gf/src/compiler/GF/Compile/ExampleBased.hs | 74 - fibon/Hackage/Gf/src/compiler/GF/Compile/Export.hs | 65 - .../Gf/src/compiler/GF/Compile/GeneratePMCFG.hs | 491 - .../Gf/src/compiler/GF/Compile/GetGrammar.hs | 52 - .../Gf/src/compiler/GF/Compile/GrammarToPGF.hs | 617 - .../Hackage/Gf/src/compiler/GF/Compile/ModDeps.hs | 145 - .../Hackage/Gf/src/compiler/GF/Compile/Optimize.hs | 229 - .../Gf/src/compiler/GF/Compile/PGFtoHaskell.hs | 229 - .../Hackage/Gf/src/compiler/GF/Compile/PGFtoJS.hs | 118 - .../Gf/src/compiler/GF/Compile/PGFtoLProlog.hs | 164 - .../Gf/src/compiler/GF/Compile/PGFtoProlog.hs | 267 - .../Gf/src/compiler/GF/Compile/ReadFiles.hs | 220 - .../Hackage/Gf/src/compiler/GF/Compile/Refresh.hs | 133 - fibon/Hackage/Gf/src/compiler/GF/Compile/Rename.hs | 318 - .../Hackage/Gf/src/compiler/GF/Compile/SubExOpt.hs | 142 - fibon/Hackage/Gf/src/compiler/GF/Compile/Update.hs | 227 - .../Hackage/Gf/src/compiler/GF/Data/BacktrackM.hs | 85 - fibon/Hackage/Gf/src/compiler/GF/Data/ErrM.hs | 38 - fibon/Hackage/Gf/src/compiler/GF/Data/Graph.hs | 178 - fibon/Hackage/Gf/src/compiler/GF/Data/Graphviz.hs | 116 - .../Hackage/Gf/src/compiler/GF/Data/Operations.hs | 374 - fibon/Hackage/Gf/src/compiler/GF/Data/Relation.hs | 193 - .../Hackage/Gf/src/compiler/GF/Data/SortedList.hs | 127 - fibon/Hackage/Gf/src/compiler/GF/Data/Str.hs | 134 - fibon/Hackage/Gf/src/compiler/GF/Data/TrieMap.hs | 66 - fibon/Hackage/Gf/src/compiler/GF/Data/Utilities.hs | 190 - fibon/Hackage/Gf/src/compiler/GF/Data/XML.hs | 57 - fibon/Hackage/Gf/src/compiler/GF/Data/Zipper.hs | 257 - fibon/Hackage/Gf/src/compiler/GF/Grammar.hs | 29 - fibon/Hackage/Gf/src/compiler/GF/Grammar/Binary.hs | 267 - fibon/Hackage/Gf/src/compiler/GF/Grammar/CF.hs | 128 - .../Hackage/Gf/src/compiler/GF/Grammar/Grammar.hs | 241 - fibon/Hackage/Gf/src/compiler/GF/Grammar/Lexer.x | 275 - .../Gf/src/compiler/GF/Grammar/Lockfield.hs | 52 - fibon/Hackage/Gf/src/compiler/GF/Grammar/Lookup.hs | 188 - .../Hackage/Gf/src/compiler/GF/Grammar/MMacros.hs | 279 - fibon/Hackage/Gf/src/compiler/GF/Grammar/Macros.hs | 627 - fibon/Hackage/Gf/src/compiler/GF/Grammar/Parser.y | 732 - .../Gf/src/compiler/GF/Grammar/PatternMatch.hs | 165 - fibon/Hackage/Gf/src/compiler/GF/Grammar/Predef.hs | 180 - .../Hackage/Gf/src/compiler/GF/Grammar/Printer.hs | 290 - .../Hackage/Gf/src/compiler/GF/Grammar/ShowTerm.hs | 40 - fibon/Hackage/Gf/src/compiler/GF/Grammar/Unify.hs | 97 - fibon/Hackage/Gf/src/compiler/GF/Grammar/Values.hs | 96 - fibon/Hackage/Gf/src/compiler/GF/Infra/CheckM.hs | 77 - .../Gf/src/compiler/GF/Infra/CompactPrint.hs | 22 - .../Gf/src/compiler/GF/Infra/Dependencies.hs | 74 - fibon/Hackage/Gf/src/compiler/GF/Infra/GetOpt.hs | 381 - fibon/Hackage/Gf/src/compiler/GF/Infra/Ident.hs | 155 - fibon/Hackage/Gf/src/compiler/GF/Infra/Modules.hs | 335 - fibon/Hackage/Gf/src/compiler/GF/Infra/Option.hs | 584 - fibon/Hackage/Gf/src/compiler/GF/Infra/UseIO.hs | 186 - .../Hackage/Gf/src/compiler/GF/JavaScript/AbsJS.hs | 61 - fibon/Hackage/Gf/src/compiler/GF/JavaScript/JS.cf | 55 - .../Hackage/Gf/src/compiler/GF/JavaScript/LexJS.x | 132 - .../Hackage/Gf/src/compiler/GF/JavaScript/Makefile | 14 - .../Hackage/Gf/src/compiler/GF/JavaScript/ParJS.y | 225 - .../Gf/src/compiler/GF/JavaScript/PrintJS.hs | 167 - fibon/Hackage/Gf/src/compiler/GF/Quiz.hs | 100 - fibon/Hackage/Gf/src/compiler/GF/Speech/CFG.hs | 372 - fibon/Hackage/Gf/src/compiler/GF/Speech/CFGToFA.hs | 244 - .../Gf/src/compiler/GF/Speech/FiniteState.hs | 329 - fibon/Hackage/Gf/src/compiler/GF/Speech/GSL.hs | 94 - fibon/Hackage/Gf/src/compiler/GF/Speech/JSGF.hs | 113 - .../Hackage/Gf/src/compiler/GF/Speech/PGFToCFG.hs | 116 - .../Hackage/Gf/src/compiler/GF/Speech/PrRegExp.hs | 27 - fibon/Hackage/Gf/src/compiler/GF/Speech/RegExp.hs | 144 - fibon/Hackage/Gf/src/compiler/GF/Speech/SISR.hs | 77 - fibon/Hackage/Gf/src/compiler/GF/Speech/SLF.hs | 178 - fibon/Hackage/Gf/src/compiler/GF/Speech/SRG.hs | 199 - .../Hackage/Gf/src/compiler/GF/Speech/SRGS_ABNF.hs | 127 - .../Hackage/Gf/src/compiler/GF/Speech/SRGS_XML.hs | 105 - .../Hackage/Gf/src/compiler/GF/Speech/VoiceXML.hs | 241 - .../Hackage/Gf/src/compiler/GF/System/NoSignal.hs | 29 - fibon/Hackage/Gf/src/compiler/GF/System/Signal.hs | 27 - .../Hackage/Gf/src/compiler/GF/System/UseSignal.hs | 72 - fibon/Hackage/Gf/src/compiler/GF/Text/Coding.hs | 69 - fibon/Hackage/Gf/src/compiler/GF/Text/Lexing.hs | 133 - .../Gf/src/compiler/GF/Text/Transliterations.hs | 212 - fibon/Hackage/Gf/src/compiler/GFC.hs | 89 - fibon/Hackage/Gf/src/compiler/GFI.hs | 380 - .../Hackage/Gf/src/runtime/haskell/Data/Binary.hs | 791 - .../Gf/src/runtime/haskell/Data/Binary/Builder.hs | 426 - .../Gf/src/runtime/haskell/Data/Binary/Get.hs | 545 - .../Gf/src/runtime/haskell/Data/Binary/Put.hs | 216 - fibon/Hackage/Gf/src/runtime/haskell/PGF.hs | 339 - fibon/Hackage/Gf/src/runtime/haskell/PGF/Binary.hs | 221 - fibon/Hackage/Gf/src/runtime/haskell/PGF/CId.hs | 55 - fibon/Hackage/Gf/src/runtime/haskell/PGF/Check.hs | 181 - fibon/Hackage/Gf/src/runtime/haskell/PGF/Data.hs | 130 - fibon/Hackage/Gf/src/runtime/haskell/PGF/Editor.hs | 241 - fibon/Hackage/Gf/src/runtime/haskell/PGF/Expr.hs | 380 - .../Gf/src/runtime/haskell/PGF/Expr.hs-boot | 28 - .../Hackage/Gf/src/runtime/haskell/PGF/Generate.hs | 117 - .../Gf/src/runtime/haskell/PGF/Linearize.hs | 108 - fibon/Hackage/Gf/src/runtime/haskell/PGF/Macros.hs | 204 - .../Gf/src/runtime/haskell/PGF/Morphology.hs | 56 - .../Gf/src/runtime/haskell/PGF/Paraphrase.hs | 112 - fibon/Hackage/Gf/src/runtime/haskell/PGF/Parse.hs | 367 - .../Hackage/Gf/src/runtime/haskell/PGF/Printer.hs | 96 - .../Gf/src/runtime/haskell/PGF/Probabilistic.hs | 72 - fibon/Hackage/Gf/src/runtime/haskell/PGF/Tree.hs | 71 - fibon/Hackage/Gf/src/runtime/haskell/PGF/Type.hs | 106 - .../Gf/src/runtime/haskell/PGF/TypeCheck.hs | 540 - .../Gf/src/runtime/haskell/PGF/VisualizeTree.hs | 353 - fibon/Hackage/HaLeX/HaLeX.stdout | 88 - .../Hackage/HaLeX/HaLeX_lib/Language/HaLex/Dfa.hs | 453 - .../HaLeX/HaLeX_lib/Language/HaLex/Dfa2MDfa.hs | 135 - .../HaLeX/HaLeX_lib/Language/HaLex/DfaMonad.lhs | 631 - .../HaLeX/HaLeX_lib/Language/HaLex/Equivalence.hs | 89 - .../HaLeX_lib/Language/HaLex/Examples/Real.lhs | 257 - .../HaLeX_lib/Language/HaLex/Examples/Robot.lhs | 124 - .../HaLeX/HaLeX_lib/Language/HaLex/Fa2RegExp.hs | 115 - .../HaLeX/HaLeX_lib/Language/HaLex/FaAsDiGraph.hs | 176 - .../HaLeX/HaLeX_lib/Language/HaLex/FaClasses.hs | 85 - .../HaLeX/HaLeX_lib/Language/HaLex/FaOperations.hs | 246 - .../HaLeX/HaLeX_lib/Language/HaLex/Minimize.hs | 207 - .../Hackage/HaLeX/HaLeX_lib/Language/HaLex/Ndfa.hs | 360 - .../HaLeX/HaLeX_lib/Language/HaLex/Parser.hs | 69 - .../HaLeX/HaLeX_lib/Language/HaLex/RegExp.hs | 264 - .../HaLeX/HaLeX_lib/Language/HaLex/RegExp2Fa.hs | 122 - .../HaLeX_lib/Language/HaLex/RegExpAsDiGraph.hs | 87 - .../HaLeX/HaLeX_lib/Language/HaLex/RegExpParser.hs | 74 - .../Hackage/HaLeX/HaLeX_lib/Language/HaLex/Util.hs | 56 - fibon/Hackage/HaLeX/HaLeX_tool/halex.hs | 155 - fibon/Hackage/HaLeX/INSTALL | 34 - fibon/Hackage/HaLeX/LICENSE | 5 - fibon/Hackage/HaLeX/Makefile | 19 - fibon/Hackage/HaLeX/README | 222 - fibon/Hackage/HaLeX/example/GenMDfa.hs | 96 - fibon/Hackage/HaLeX/example/README | 51 - fibon/Hackage/HaLeX/example/real | 1 - fibon/Hackage/HaLeX/example/real_dfa.hs | 88 - fibon/Hackage/HaLeX/example/real_dfa.ps | 350 - fibon/Hackage/HaLeX/example/real_ndfa.hs | 142 - fibon/Hackage/HaLeX/example/real_ndfa.ps | 3615 - fibon/Hackage/HaLeX/real | 1 - fibon/Hackage/HaLeX/scripts/Make_Animation | 6 - fibon/Hackage/HaLeX/scripts/faAnim.lefty | 282 - fibon/Hackage/Happy/ANNOUNCE | 27 - fibon/Hackage/Happy/Bio.y | 409 - fibon/Hackage/Happy/CHANGES | 168 - fibon/Hackage/Happy/ErlParser.ly | 391 - fibon/Hackage/Happy/Happy.stderr | 8 - fibon/Hackage/Happy/HappyTemplate | 204 - fibon/Hackage/Happy/HaskellParser.y | 650 - fibon/Hackage/Happy/LICENSE | 30 - fibon/Hackage/Happy/Makefile | 24 - fibon/Hackage/Happy/README | 27 - fibon/Hackage/Happy/TODO | 59 - fibon/Hackage/Happy/TestInput.hs.expected | 20981 - fibon/Hackage/Happy/TestInput.y | 1927 - fibon/Hackage/Happy/generated/AttrGrammarParser.hs | 612 - fibon/Hackage/Happy/generated/Parser.hs | 999 - fibon/Hackage/Happy/generated/Paths_happy.hs | 29 - fibon/Hackage/Happy/happy.spec | 63 - fibon/Hackage/Happy/happy.stderr.expected | 8 - fibon/Hackage/Happy/src/ARRAY-NOTES | 40 - fibon/Hackage/Happy/src/AbsSyn.lhs | 137 - fibon/Hackage/Happy/src/AttrGrammar.lhs | 107 - fibon/Hackage/Happy/src/AttrGrammarParser.ly | 68 - fibon/Hackage/Happy/src/First.lhs | 67 - fibon/Hackage/Happy/src/GenUtils.lhs | 224 - fibon/Hackage/Happy/src/Grammar.lhs | 594 - fibon/Hackage/Happy/src/Info.lhs | 213 - fibon/Hackage/Happy/src/LALR.lhs | 662 - fibon/Hackage/Happy/src/Lexer.lhs | 251 - fibon/Hackage/Happy/src/Main.lhs | 590 - fibon/Hackage/Happy/src/NameSet.hs | 10 - fibon/Hackage/Happy/src/ParamRules.hs | 92 - fibon/Hackage/Happy/src/ParseMonad.lhs | 22 - fibon/Hackage/Happy/src/Parser.ly | 146 - fibon/Hackage/Happy/src/ProduceCode.lhs | 1210 - fibon/Hackage/Happy/src/ProduceGLRCode.lhs | 701 - fibon/Hackage/Happy/src/Target.lhs | 13 - fibon/Hackage/Happy/templates/GLR_Base.hs | 84 - fibon/Hackage/Happy/templates/GLR_Lib.hs | 453 - fibon/Hackage/Happy/templates/GenericTemplate.hs | 320 - fibon/Hackage/Hgalib/Chromosome/ANN.hs | 142 - fibon/Hackage/Hgalib/Chromosome/Bits.hs | 53 - fibon/Hackage/Hgalib/Chromosome/GP.hs | 88 - fibon/Hackage/Hgalib/GA.hs | 142 - fibon/Hackage/Hgalib/Hgalib.stdout | 2 - fibon/Hackage/Hgalib/LICENSE | 1 - fibon/Hackage/Hgalib/Makefile | 9 - fibon/Hackage/Hgalib/Population/Array.hs | 101 - fibon/Hackage/Hgalib/Population/List.hs | 81 - fibon/Hackage/Hgalib/README | 13 - fibon/Hackage/Hgalib/examples/ANNTest.hs | 70 - fibon/Hackage/Hgalib/examples/BitTest.hs | 64 - fibon/Hackage/Hgalib/examples/GPTest.hs | 78 - fibon/Hackage/Makefile | 12 - fibon/Hackage/Palindromes/CREDITS | 22 - fibon/Hackage/Palindromes/LICENSE | 28 - fibon/Hackage/Palindromes/Makefile | 8 - fibon/Hackage/Palindromes/Palindromes.stdout | 4 - fibon/Hackage/Palindromes/README | 116 - fibon/Hackage/Palindromes/RELEASE_HISTORY | 15 - fibon/Hackage/Palindromes/annakarenina.txt | 43589 -- fibon/Hackage/Palindromes/huckfinn.txt | 11720 - fibon/Hackage/Palindromes/olivertwist.txt | 19203 - .../src/Data/Algorithms/Palindromes/Main.hs | 48 - .../src/Data/Algorithms/Palindromes/Options.hs | 113 - .../src/Data/Algorithms/Palindromes/Palindromes.hs | 333 - fibon/Hackage/Palindromes/swannsway.txt | 17478 - fibon/Hackage/Pappy/Blowfish.java | 1369 - fibon/Hackage/Pappy/CAST5.java | 1323 - fibon/Hackage/Pappy/DES.java | 1237 - fibon/Hackage/Pappy/LICENSE | 30 - fibon/Hackage/Pappy/Makefile | 8 - fibon/Hackage/Pappy/Pappy.stdout | 7 - fibon/Hackage/Pappy/SPEED.java | 1393 - fibon/Hackage/Pappy/Scar.java | 1527 - fibon/Hackage/Pappy/TestRijndael.java | 1055 - fibon/Hackage/Pappy/examples/Arith.hs | 292 - fibon/Hackage/Pappy/examples/Arith.pappy | 67 - fibon/Hackage/Pappy/examples/Java.hs | 3447 - fibon/Hackage/Pappy/examples/Java.pappy | 727 - .../testsuite-java/BlockMessageDigest.java | 213 - .../Pappy/examples/testsuite-java/Blowfish.java | 1369 - .../Pappy/examples/testsuite-java/CAST5.java | 1323 - .../Hackage/Pappy/examples/testsuite-java/DES.java | 1237 - .../Pappy/examples/testsuite-java/DES2X.java | 262 - .../Pappy/examples/testsuite-java/DESX.java | 251 - .../Pappy/examples/testsuite-java/DES_EDE3.java | 248 - .../Pappy/examples/testsuite-java/HAVAL.java | 823 - .../Pappy/examples/testsuite-java/HexDump.java | 30 - .../Pappy/examples/testsuite-java/IDEA.java | 704 - .../Hackage/Pappy/examples/testsuite-java/KAT.java | 737 - .../Pappy/examples/testsuite-java/LOKI91.java | 676 - .../Hackage/Pappy/examples/testsuite-java/MCT.java | 1046 - .../Hackage/Pappy/examples/testsuite-java/MD2.java | 289 - .../Hackage/Pappy/examples/testsuite-java/MD4.java | 314 - .../Hackage/Pappy/examples/testsuite-java/MD5.java | 483 - .../Pappy/examples/testsuite-java/NativeLink.java | 408 - .../Hackage/Pappy/examples/testsuite-java/RC2.java | 562 - .../Hackage/Pappy/examples/testsuite-java/RC4.java | 462 - .../Pappy/examples/testsuite-java/RIPEMD128.java | 402 - .../Pappy/examples/testsuite-java/RIPEMD160.java | 428 - .../Pappy/examples/testsuite-java/Rijndael.java | 564 - .../Pappy/examples/testsuite-java/SAFER.java | 874 - .../Pappy/examples/testsuite-java/SHA0.java | 490 - .../Pappy/examples/testsuite-java/SHA1.java | 475 - .../Pappy/examples/testsuite-java/SPEED.java | 1393 - .../Pappy/examples/testsuite-java/Scar.java | 1527 - .../Pappy/examples/testsuite-java/Square.java | 823 - .../Pappy/examples/testsuite-java/Test3LFSR.java | 265 - .../Pappy/examples/testsuite-java/TestAll.java | 172 - .../Pappy/examples/testsuite-java/TestBR.java | 246 - .../examples/testsuite-java/TestBase64Stream.java | 141 - .../examples/testsuite-java/TestBlowfish.java | 293 - .../Pappy/examples/testsuite-java/TestCAST5.java | 198 - .../Pappy/examples/testsuite-java/TestDES.java | 336 - .../examples/testsuite-java/TestDES_EDE3.java | 222 - .../Pappy/examples/testsuite-java/TestElGamal.java | 208 - .../Pappy/examples/testsuite-java/TestHAVAL.java | 254 - .../Pappy/examples/testsuite-java/TestHMAC.java | 165 - .../Pappy/examples/testsuite-java/TestIDEA.java | 172 - .../Pappy/examples/testsuite-java/TestIJCE.java | 258 - .../Pappy/examples/testsuite-java/TestInstall.java | 81 - .../Pappy/examples/testsuite-java/TestLOKI91.java | 397 - .../Pappy/examples/testsuite-java/TestMD2.java | 108 - .../Pappy/examples/testsuite-java/TestMD4.java | 108 - .../Pappy/examples/testsuite-java/TestMD5.java | 171 - .../Pappy/examples/testsuite-java/TestRC2.java | 197 - .../Pappy/examples/testsuite-java/TestRC4.java | 183 - .../examples/testsuite-java/TestRIPEMD128.java | 126 - .../examples/testsuite-java/TestRIPEMD160.java | 125 - .../Pappy/examples/testsuite-java/TestRSA.java | 309 - .../examples/testsuite-java/TestRijndael.java | 1055 - .../Pappy/examples/testsuite-java/TestSAFER.java | 796 - .../Pappy/examples/testsuite-java/TestSHA0.java | 157 - .../Pappy/examples/testsuite-java/TestSHA1.java | 161 - .../Pappy/examples/testsuite-java/TestSPEED.java | 191 - .../Pappy/examples/testsuite-java/TestScar.java | 190 - .../Pappy/examples/testsuite-java/TestSquare.java | 282 - .../examples/testsuite-java/TestUnixCrypt.java | 85 - .../Pappy/examples/testsuite-java/UnixCrypt.java | 306 - fibon/Hackage/Pappy/java-parser/JavaMonad.hs | 1046 - fibon/Hackage/Pappy/src/Main.hs | 56 - fibon/Hackage/Pappy/src/MemoAnalysis.hs | 147 - fibon/Hackage/Pappy/src/Pappy.hs | 178 - fibon/Hackage/Pappy/src/Parse.hs | 410 - fibon/Hackage/Pappy/src/Pos.hs | 47 - fibon/Hackage/Pappy/src/ReadGrammar.hs | 400 - fibon/Hackage/Pappy/src/ReduceGrammar.hs | 293 - fibon/Hackage/Pappy/src/SimplifyGrammar.hs | 424 - fibon/Hackage/Pappy/src/WriteParser.hs | 570 - fibon/Hackage/QuickCheck/LICENSE | 27 - fibon/Hackage/QuickCheck/Makefile | 20 - fibon/Hackage/QuickCheck/QuickCheck.stdout | 1 - fibon/Hackage/QuickCheck/README | 26 - fibon/Hackage/QuickCheck/Test/QuickCheck.hs | 105 - .../QuickCheck/Test/QuickCheck/Arbitrary.hs | 536 - .../QuickCheck/Test/QuickCheck/Exception.hs | 72 - .../Hackage/QuickCheck/Test/QuickCheck/Function.hs | 257 - fibon/Hackage/QuickCheck/Test/QuickCheck/Gen.hs | 179 - .../QuickCheck/Test/QuickCheck/Modifiers.hs | 232 - .../Hackage/QuickCheck/Test/QuickCheck/Monadic.hs | 85 - fibon/Hackage/QuickCheck/Test/QuickCheck/Poly.hs | 110 - .../Hackage/QuickCheck/Test/QuickCheck/Property.hs | 342 - fibon/Hackage/QuickCheck/Test/QuickCheck/State.hs | 33 - fibon/Hackage/QuickCheck/Test/QuickCheck/Test.hs | 367 - fibon/Hackage/QuickCheck/Test/QuickCheck/Text.hs | 148 - fibon/Hackage/QuickCheck/examples/ExFol.hs | 276 - fibon/Hackage/QuickCheck/examples/ExHeap.hs | 174 - fibon/Hackage/QuickCheck/examples/ExLambda.hs | 362 - fibon/Hackage/QuickCheck/examples/ExMerge.hs | 116 - fibon/Hackage/QuickCheck/examples/ExSet.hs | 222 - fibon/Hackage/QuickCheck/examples/ExSet2.hs | 161 - fibon/Hackage/QuickCheck/examples/ExSimple.hs | 39 - fibon/Hackage/QuickCheck/examples/ExTrie.hs | 213 - fibon/Hackage/QuickCheck/examples/ExWeird.hs | 52 - fibon/Hackage/QuickCheck/examples/ExWords.hs | 50 - fibon/Hackage/QuickCheck/examples/Example1.hs | 165 - fibon/Hackage/QuickCheck/examples/Example2.hs | 53 - fibon/Hackage/QuickCheck/examples/Main.hs | 41 - fibon/Hackage/QuickCheck/examples/Set.hs | 97 - fibon/Hackage/Regex/LICENSE | 12 - fibon/Hackage/Regex/Makefile | 31 - fibon/Hackage/Regex/Regex.stdout | 50 - .../Hackage/Regex/Text/Regex/PDeriv/ByteString.lhs | 31 - .../Text/Regex/PDeriv/ByteString/LeftToRight.lhs | 437 - .../Text/Regex/PDeriv/ByteString/LeftToRightD.lhs | 511 - .../Regex/Text/Regex/PDeriv/ByteString/Posix.lhs | 610 - .../Text/Regex/PDeriv/ByteString/RightToLeft.lhs | 356 - .../Text/Regex/PDeriv/ByteString/TwoPasses.lhs | 385 - fibon/Hackage/Regex/Text/Regex/PDeriv/Common.lhs | 125 - .../Hackage/Regex/Text/Regex/PDeriv/Dictionary.hs | 156 - .../Hackage/Regex/Text/Regex/PDeriv/ExtPattern.lhs | 37 - .../Hackage/Regex/Text/Regex/PDeriv/IntPattern.lhs | 312 - fibon/Hackage/Regex/Text/Regex/PDeriv/Nfa.lhs | 80 - fibon/Hackage/Regex/Text/Regex/PDeriv/Parse.lhs | 152 - fibon/Hackage/Regex/Text/Regex/PDeriv/Pretty.lhs | 4 - fibon/Hackage/Regex/Text/Regex/PDeriv/RE.lhs | 148 - .../Hackage/Regex/Text/Regex/PDeriv/Translate.lhs | 484 - fibon/Hackage/Regex/Text/Regex/PDeriv/Word.lhs | 12 - fibon/Hackage/Regex/addr.txt | 50000 -- fibon/Hackage/Regex/bench/Main.hs | 59 - fibon/Hackage/Regex/bitset/Data/BitSet.hs | 89 - fibon/Hackage/Regex/bitset/LICENSE | 165 - fibon/Hackage/Regex/bitset/Setup.hs | 2 - fibon/Hackage/Regex/bitset/bitset.cabal | 23 - fibon/Hackage/Regex/bitset/tests/Properties.hs | 89 - fibon/Hackage/Regex/deepseq/Control/DeepSeq.hs | 190 - fibon/Hackage/Regex/deepseq/LICENSE | 39 - fibon/Hackage/Regex/deepseq/Setup.hs | 6 - fibon/Hackage/Regex/deepseq/deepseq.cabal | 24 - fibon/Hackage/Regex/parsec/LICENSE | 21 - fibon/Hackage/Regex/parsec/Setup.hs | 6 - .../Regex/parsec/Text/ParserCombinators/Parsec.hs | 54 - .../parsec/Text/ParserCombinators/Parsec/Char.hs | 75 - .../Text/ParserCombinators/Parsec/Combinator.hs | 155 - .../parsec/Text/ParserCombinators/Parsec/Error.hs | 164 - .../parsec/Text/ParserCombinators/Parsec/Expr.hs | 123 - .../Text/ParserCombinators/Parsec/Language.hs | 124 - .../parsec/Text/ParserCombinators/Parsec/Perm.hs | 122 - .../parsec/Text/ParserCombinators/Parsec/Pos.hs | 99 - .../parsec/Text/ParserCombinators/Parsec/Prim.hs | 456 - .../parsec/Text/ParserCombinators/Parsec/Token.hs | 473 - fibon/Hackage/Regex/parsec/parsec.cabal | 35 - fibon/Hackage/Regex/regex-base/LICENSE | 12 - fibon/Hackage/Regex/regex-base/Setup.hs | 2 - fibon/Hackage/Regex/regex-base/Text/Regex/Base.hs | 56 - .../Regex/regex-base/Text/Regex/Base/Context.hs | 409 - .../Regex/regex-base/Text/Regex/Base/Impl.hs | 58 - .../Regex/regex-base/Text/Regex/Base/RegexLike.hs | 228 - fibon/Hackage/Regex/regex-base/regex-base.cabal | 58 - fibon/Hackage/Simgi/.gitignore | 10 - fibon/Hackage/Simgi/AUTHORS | 3 - fibon/Hackage/Simgi/COPYING | 674 - fibon/Hackage/Simgi/ChangeLog | 41 - fibon/Hackage/Simgi/INSTALL | 18 - fibon/Hackage/Simgi/Makefile | 36 - fibon/Hackage/Simgi/Models/brusselator.sgl | 30 - fibon/Hackage/Simgi/Models/irreversible_bimol.sgl | 21 - fibon/Hackage/Simgi/Models/irreversible_trimol.sgl | 38 - fibon/Hackage/Simgi/Models/oregonator.sgl | 32 - fibon/Hackage/Simgi/Models/reversible_bimol.sgl | 29 - fibon/Hackage/Simgi/Models/reversible_trimol.sgl | 39 - fibon/Hackage/Simgi/Models/volterra.sgl | 29 - fibon/Hackage/Simgi/README | 15 - fibon/Hackage/Simgi/Simgi.stdout | 1 - fibon/Hackage/Simgi/doc/Makefile | 12 - fibon/Hackage/Simgi/doc/simgi.html | 687 - fibon/Hackage/Simgi/doc/simgi.mdml | 425 - fibon/Hackage/Simgi/doc/simgi.pdf | Bin 174168 -> 0 bytes fibon/Hackage/Simgi/mersenne-random-pure64/LICENSE | 30 - .../mersenne-random-pure64/LICENSE.mt19937-64 | 54 - .../Hackage/Simgi/mersenne-random-pure64/Setup.lhs | 3 - .../System/Random/Mersenne/Pure64.hs | 127 - .../System/Random/Mersenne/Pure64/Base.hsc | 78 - .../System/Random/Mersenne/Pure64/MTBlock.hs | 94 - fibon/Hackage/Simgi/mersenne-random-pure64/TODO | 17 - .../cbits/mt19937-64-block.c | 99 - .../cbits/mt19937-64-unsafe.c | 122 - .../mersenne-random-pure64/cbits/mt19937-64.c | 116 - .../include/mt19937-64-block.h | 73 - .../include/mt19937-64-unsafe.h | 64 - .../mersenne-random-pure64/include/mt19937-64.h | 76 - .../mersenne-random-pure64.cabal | 59 - .../Simgi/mersenne-random-pure64/tests/Unit.hs | 165 - .../Simgi/mersenne-random-pure64/tests/copy.hs | 15 - fibon/Hackage/Simgi/oregonator.sgl | 32 - fibon/Hackage/Simgi/oregonator_output.dat.expected | 36 - fibon/Hackage/Simgi/parsec-2/LICENSE | 21 - fibon/Hackage/Simgi/parsec-2/Setup.hs | 6 - .../parsec-2/Text/ParserCombinators/Parsec.hs | 54 - .../parsec-2/Text/ParserCombinators/Parsec/Char.hs | 75 - .../Text/ParserCombinators/Parsec/Combinator.hs | 155 - .../Text/ParserCombinators/Parsec/Error.hs | 164 - .../parsec-2/Text/ParserCombinators/Parsec/Expr.hs | 123 - .../Text/ParserCombinators/Parsec/Language.hs | 124 - .../parsec-2/Text/ParserCombinators/Parsec/Perm.hs | 122 - .../parsec-2/Text/ParserCombinators/Parsec/Pos.hs | 99 - .../parsec-2/Text/ParserCombinators/Parsec/Prim.hs | 456 - .../Text/ParserCombinators/Parsec/Token.hs | 473 - fibon/Hackage/Simgi/parsec-2/parsec.cabal | 35 - fibon/Hackage/Simgi/src/CommandLine.hs | 123 - fibon/Hackage/Simgi/src/Engine.hs | 360 - fibon/Hackage/Simgi/src/ExtraFunctions.hs | 197 - fibon/Hackage/Simgi/src/GenericModel.hs | 296 - fibon/Hackage/Simgi/src/IO.hs | 76 - fibon/Hackage/Simgi/src/InputCheck.hs | 235 - fibon/Hackage/Simgi/src/InputParser.hs | 591 - fibon/Hackage/Simgi/src/Messages.hs | 83 - fibon/Hackage/Simgi/src/PrettyPrint.hs | 75 - fibon/Hackage/Simgi/src/RpnCalc.hs | 110 - fibon/Hackage/Simgi/src/RpnData.hs | 101 - fibon/Hackage/Simgi/src/RpnParser.hs | 195 - fibon/Hackage/Simgi/src/TokenParser.hs | 232 - fibon/Hackage/Simgi/src/simgi.hs | 89 - fibon/Hackage/TernaryTrees/Data/Map/StringMap.hs | 107 - fibon/Hackage/TernaryTrees/Data/Map/TernaryMap.hs | 225 - .../TernaryTrees/Data/Map/TernaryMap/Internal.hs | 12 - fibon/Hackage/TernaryTrees/Data/Set/StringSet.hs | 138 - .../TernaryTrees/Data/Set/StringSet/Internal.hs | 25 - fibon/Hackage/TernaryTrees/Data/Set/TernarySet.hs | 147 - .../TernaryTrees/Data/Set/TernarySet/Internal.hs | 18 - fibon/Hackage/TernaryTrees/LICENSE.txt | 23 - fibon/Hackage/TernaryTrees/Main.hs | 50 - fibon/Hackage/TernaryTrees/Makefile | 10 - fibon/Hackage/TernaryTrees/TernaryTrees.stdout | 469879 ------------------ fibon/Hackage/TernaryTrees/olivertwist.txt | 19203 - fibon/Hackage/TernaryTrees/words | 234936 --------- fibon/Hackage/Xsact/LICENSE | 340 - fibon/Hackage/Xsact/Makefile | 17 - fibon/Hackage/Xsact/Xsact.stdout | 79 - fibon/Hackage/Xsact/doc/xsact.1 | 73 - fibon/Hackage/Xsact/pdbnt | 31752 -- fibon/Hackage/Xsact/src/ANSI.lhs | 75 - fibon/Hackage/Xsact/src/Clix.lhs | 48 - fibon/Hackage/Xsact/src/Cluster.lhs | 244 - fibon/Hackage/Xsact/src/EST.lhs | 100 - fibon/Hackage/Xsact/src/Fasta.lhs | 138 - fibon/Hackage/Xsact/src/Gene.hs | 59 - fibon/Hackage/Xsact/src/Indexed.lhs | 40 - fibon/Hackage/Xsact/src/Pairs.lhs | 675 - fibon/Hackage/Xsact/src/SpliceGraph.lhs | 524 - fibon/Hackage/Xsact/src/Stats.hs | 125 - fibon/Hackage/Xsact/src/Suffix.lhs | 86 - fibon/Hackage/Xsact/src/Util.hs | 30 - fibon/Hackage/Xsact/src/WordMap.lhs | 198 - fibon/Hackage/Xsact/src/Xplit.lhs | 43 - fibon/Hackage/Xsact/src/Xsact.lhs | 278 - fibon/Hackage/Xsact/src/Xtract.lhs | 120 - fibon/Hackage/Xsact/src/hooks.c | 17 - fibon/Hackage/Xsact/test-xsact/bigtest.sh | 75 - fibon/Hackage/Xsact/test-xsact/test.seq | 74 - fibon/Hackage/Xsact/test-xsact/test.sh | 132 - fibon/Hackage/Xsact/test-xsact/time.sh | 37 - fibon/Hackage/Xsact/test-xtract/ignN.seq | 9 - fibon/Hackage/Xsact/test-xtract/jump.seq | 7 - fibon/Hackage/Xsact/test-xtract/loop.seq | 5 - fibon/Hackage/Xsact/test-xtract/repword.seq | 11 - fibon/Hackage/Xsact/test-xtract/single.seq | 3 - fibon/Hackage/Xsact/test-xtract/test.sh | 29 - fibon/Hackage/Xsact/test-xtract/xtract.std | 20 - fibon/Makefile | 7 - fibon/Repa/Blur/Blur.stdout | 1 - fibon/Repa/Blur/Main.hs | 99 - fibon/Repa/Blur/Makefile | 76 - fibon/Repa/Blur/lena.bmp | Bin 786486 -> 0 bytes fibon/Repa/Canny/Canny.stdout | 1 - fibon/Repa/Canny/Main.hs | 385 - fibon/Repa/Canny/Makefile | 76 - fibon/Repa/Canny/lena.bmp | Bin 786486 -> 0 bytes fibon/Repa/FFT3d/FFT3d.stdout | 1 - fibon/Repa/FFT3d/Main.hs | 106 - fibon/Repa/FFT3d/Makefile | 76 - fibon/Repa/FFTHighPass2d/FFTHighPass2d.stdout | 1 - fibon/Repa/FFTHighPass2d/Main.hs | 92 - fibon/Repa/FFTHighPass2d/Makefile | 76 - fibon/Repa/FFTHighPass2d/lena.bmp | Bin 786486 -> 0 bytes fibon/Repa/Laplace/Laplace.stdout | 1 - fibon/Repa/Laplace/Main.hs | 182 - fibon/Repa/Laplace/Makefile | 77 - fibon/Repa/Laplace/SolverGet.hs | 74 - fibon/Repa/Laplace/SolverStencil.hs | 51 - fibon/Repa/Laplace/pls-400x400.bmp | Bin 640122 -> 0 bytes fibon/Repa/MMult/MMult.stdout | 1 - fibon/Repa/MMult/Main.hs | 109 - fibon/Repa/MMult/Makefile | 74 - fibon/Repa/Makefile | 9 - fibon/Repa/Sobel/Main.hs | 86 - fibon/Repa/Sobel/Makefile | 77 - fibon/Repa/Sobel/Sobel.stdout | 1 - fibon/Repa/Sobel/Solver.hs | 35 - fibon/Repa/Sobel/lena.bmp | Bin 786486 -> 0 bytes fibon/Repa/Volume/Main.hs | 97 - fibon/Repa/Volume/Makefile | 76 - fibon/Repa/Volume/lena.bmp | Bin 786486 -> 0 bytes fibon/Repa/_RepaLib/Makefile | 84 - fibon/Repa/_RepaLib/bmp/Codec/BMP.hs | 191 - fibon/Repa/_RepaLib/bmp/Codec/BMP/Base.hs | 21 - fibon/Repa/_RepaLib/bmp/Codec/BMP/BitmapInfo.hs | 60 - fibon/Repa/_RepaLib/bmp/Codec/BMP/BitmapInfoV3.hs | 171 - fibon/Repa/_RepaLib/bmp/Codec/BMP/BitmapInfoV4.hs | 190 - fibon/Repa/_RepaLib/bmp/Codec/BMP/BitmapInfoV5.hs | 75 - fibon/Repa/_RepaLib/bmp/Codec/BMP/CIEXYZ.hs | 27 - fibon/Repa/_RepaLib/bmp/Codec/BMP/Compression.hs | 43 - fibon/Repa/_RepaLib/bmp/Codec/BMP/Error.hs | 60 - fibon/Repa/_RepaLib/bmp/Codec/BMP/FileHeader.hs | 90 - fibon/Repa/_RepaLib/bmp/Codec/BMP/Pack.hs | 133 - fibon/Repa/_RepaLib/bmp/Codec/BMP/Unpack.hs | 132 - fibon/Repa/_RepaLib/bmp/LICENSE | 13 - fibon/Repa/_RepaLib/bmp/Setup.hs | 2 - fibon/Repa/_RepaLib/quickcheck/LICENSE | 28 - fibon/Repa/_RepaLib/quickcheck/README | 30 - fibon/Repa/_RepaLib/quickcheck/Setup.lhs | 8 - fibon/Repa/_RepaLib/quickcheck/Test/QuickCheck.hs | 120 - .../_RepaLib/quickcheck/Test/QuickCheck/All.hs | 121 - .../quickcheck/Test/QuickCheck/Arbitrary.hs | 527 - .../quickcheck/Test/QuickCheck/Exception.hs | 75 - .../quickcheck/Test/QuickCheck/Function.hs | 302 - .../_RepaLib/quickcheck/Test/QuickCheck/Gen.hs | 172 - .../quickcheck/Test/QuickCheck/Modifiers.hs | 271 - .../_RepaLib/quickcheck/Test/QuickCheck/Monadic.hs | 92 - .../_RepaLib/quickcheck/Test/QuickCheck/Poly.hs | 134 - .../quickcheck/Test/QuickCheck/Property.hs | 431 - .../_RepaLib/quickcheck/Test/QuickCheck/State.hs | 33 - .../_RepaLib/quickcheck/Test/QuickCheck/Test.hs | 389 - .../_RepaLib/quickcheck/Test/QuickCheck/Text.hs | 148 - .../Data/Array/Repa/Algorithms/Complex.hs | 67 - .../Data/Array/Repa/Algorithms/Convolve.hs | 167 - .../Data/Array/Repa/Algorithms/DFT.hs | 101 - .../Data/Array/Repa/Algorithms/DFT/Center.hs | 33 - .../Data/Array/Repa/Algorithms/DFT/Roots.hs | 44 - .../Data/Array/Repa/Algorithms/FFT.hs | 201 - .../Data/Array/Repa/Algorithms/Iterate.hs | 45 - .../Data/Array/Repa/Algorithms/Matrix.hs | 41 - .../Data/Array/Repa/Algorithms/Randomish.hs | 115 - fibon/Repa/_RepaLib/repa-algorithms/LICENSE | 24 - fibon/Repa/_RepaLib/repa-algorithms/Setup.hs | 2 - .../repa-bytestring/Data/Array/Repa/ByteString.hs | 101 - fibon/Repa/_RepaLib/repa-bytestring/LICENSE | 24 - fibon/Repa/_RepaLib/repa-bytestring/Setup.hs | 2 - .../_RepaLib/repa-io/Data/Array/Repa/IO/BMP.hs | 230 - .../_RepaLib/repa-io/Data/Array/Repa/IO/Binary.hs | 83 - .../repa-io/Data/Array/Repa/IO/ColorRamp.hs | 48 - .../repa-io/Data/Array/Repa/IO/Internals/Text.hs | 41 - .../_RepaLib/repa-io/Data/Array/Repa/IO/Matrix.hs | 70 - .../_RepaLib/repa-io/Data/Array/Repa/IO/Timing.hs | 86 - .../_RepaLib/repa-io/Data/Array/Repa/IO/Vector.hs | 74 - fibon/Repa/_RepaLib/repa-io/LICENSE | 24 - fibon/Repa/_RepaLib/repa-io/Setup.hs | 2 - fibon/Repa/_RepaLib/repa/Data/Array/Repa.hs | 209 - .../_RepaLib/repa/Data/Array/Repa/Arbitrary.hs | 99 - fibon/Repa/_RepaLib/repa/Data/Array/Repa/Index.hs | 145 - .../repa/Data/Array/Repa/Internals/Base.hs | 410 - .../_RepaLib/repa/Data/Array/Repa/Internals/Elt.hs | 283 - .../Data/Array/Repa/Internals/EvalBlockwise.hs | 153 - .../repa/Data/Array/Repa/Internals/EvalChunked.hs | 62 - .../repa/Data/Array/Repa/Internals/EvalCursored.hs | 136 - .../Data/Array/Repa/Internals/EvalReduction.hs | 121 - .../repa/Data/Array/Repa/Internals/Forcing.hs | 215 - .../repa/Data/Array/Repa/Internals/Gang.hs | 249 - .../repa/Data/Array/Repa/Internals/Select.hs | 118 - .../repa/Data/Array/Repa/Operators/IndexSpace.hs | 165 - .../repa/Data/Array/Repa/Operators/Interleave.hs | 111 - .../repa/Data/Array/Repa/Operators/Mapping.hs | 109 - .../repa/Data/Array/Repa/Operators/Modify.hs | 53 - .../repa/Data/Array/Repa/Operators/Reduction.hs | 82 - .../repa/Data/Array/Repa/Operators/Select.hs | 44 - .../repa/Data/Array/Repa/Operators/Traverse.hs | 126 - .../_RepaLib/repa/Data/Array/Repa/Properties.hs | 115 - fibon/Repa/_RepaLib/repa/Data/Array/Repa/Shape.hs | 82 - fibon/Repa/_RepaLib/repa/Data/Array/Repa/Slice.hs | 83 - .../repa/Data/Array/Repa/Specialised/Dim2.hs | 108 - .../Repa/_RepaLib/repa/Data/Array/Repa/Stencil.hs | 270 - .../_RepaLib/repa/Data/Array/Repa/Stencil/Base.hs | 59 - .../repa/Data/Array/Repa/Stencil/Template.hs | 95 - fibon/Repa/_RepaLib/repa/LICENSE | 24 - fibon/Repa/_RepaLib/repa/Setup.hs | 2 - .../Shootout/ChameneosRedux/ChameneosRedux.stdout | 16 - fibon/Shootout/ChameneosRedux/LICENSE | 30 - fibon/Shootout/ChameneosRedux/Makefile | 6 - fibon/Shootout/ChameneosRedux/chameneosredux.hs | 96 - fibon/Shootout/Fannkuch/Fannkuch.stdout | 31 - fibon/Shootout/Fannkuch/LICENSE | 30 - fibon/Shootout/Fannkuch/Makefile | 6 - fibon/Shootout/Fannkuch/fannkuch.hs | 27 - fibon/Shootout/Makefile | 11 - fibon/Shootout/Mandelbrot/LICENSE | 30 - fibon/Shootout/Mandelbrot/Makefile | 6 - fibon/Shootout/Mandelbrot/Mandelbrot.stdout | Bin 1529513 -> 0 bytes fibon/Shootout/Mandelbrot/mandelbrot.hs | 68 - 1294 files changed, 1737302 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 50812b141f1a6c372c85cceb3541e9c1c7bab926 From git at git.haskell.org Wed Jun 7 18:54:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Jun 2017 18:54:46 +0000 (UTC) Subject: [commit: nofib] master: Simplify some shootout Makefiles (eccf532) Message-ID: <20170607185446.8BEEC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eccf532410eee45f30c07f389f7029871fd603db/nofib >--------------------------------------------------------------- commit eccf532410eee45f30c07f389f7029871fd603db Author: Michal Terepeta Date: Wed Jun 7 14:54:34 2017 -0400 Simplify some shootout Makefiles Summary: By following the naming conventions of the build system we can simplify the `Makefile`s a bit. This patch also avoids having to explicitly pass the flags to `runstdtest` for `fasta`, `k-nucleotide` and `reverse-complement`. The only consquence of this is that it's a requirement to run `make boot` before `make` for these benchmarks. But that is already the case since `.depend` files are generated by with `make boot`. Finally, this also update the `.gitignore` with the new names of the output/input files. Signed-off-by: Michal Terepeta Test Plan: build & run Reviewers: bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D3412 >--------------------------------------------------------------- eccf532410eee45f30c07f389f7029871fd603db .gitignore | 12 +++++------ shootout/fasta/Makefile | 10 ++++----- shootout/k-nucleotide/Makefile | 19 +++++++++-------- shootout/reverse-complement/Makefile | 41 +++++++++++++++++------------------- 4 files changed, 39 insertions(+), 43 deletions(-) diff --git a/.gitignore b/.gitignore index 24e76f2..c5604e8 100644 --- a/.gitignore +++ b/.gitignore @@ -62,16 +62,16 @@ shootout/fasta/fasta.slowstdout shootout/fasta/fasta.stdout shootout/k-nucleotide/fasta-c shootout/k-nucleotide/k-nucleotide -shootout/k-nucleotide/knucleotide-input250000.txt -shootout/k-nucleotide/knucleotide-input2500000.txt -shootout/k-nucleotide/knucleotide-input25000000.txt +shootout/k-nucleotide/k-nucleotide.faststdin +shootout/k-nucleotide/k-nucleotide.slowstdin +shootout/k-nucleotide/k-nucleotide.stdin shootout/n-body/n-body shootout/pidigits/pidigits shootout/reverse-complement/fasta-c shootout/reverse-complement/revcomp-c -shootout/reverse-complement/revcomp-input250000.txt -shootout/reverse-complement/revcomp-input2500000.txt -shootout/reverse-complement/revcomp-input25000000.txt +shootout/reverse-complement/reverse-complement.faststdin +shootout/reverse-complement/reverse-complement.slowstdin +shootout/reverse-complement/reverse-complement.stdin shootout/reverse-complement/reverse-complement shootout/reverse-complement/reverse-complement.faststdout shootout/reverse-complement/reverse-complement.slowstdout diff --git a/shootout/fasta/Makefile b/shootout/fasta/Makefile index 447b3a8..68e6279 100644 --- a/shootout/fasta/Makefile +++ b/shootout/fasta/Makefile @@ -28,9 +28,9 @@ fasta.stdout : fasta-c fasta.slowstdout : fasta-c ./fasta-c $(SLOW_OPTS) > $@ -# Since the stdout files are created during the run the runstdtest -# script doesn't correctly pick them up, so we have to specify them -# explicitly here. +# Since we only decide here what the INPUT_FILE is, it's required to first run +# `make boot` and only than `make` (otherwise `make` doesn't "see" the file and +# doesn't call `runstdtest` correctly) ifeq "$(mode)" "slow" STDOUT_FILE = fasta.slowstdout else @@ -41,8 +41,6 @@ else endif endif -SRC_RUNTEST_OPTS += -o1 $(STDOUT_FILE) - -all boot :: $(STDOUT_FILE) +boot :: $(STDOUT_FILE) include $(TOP)/mk/target.mk diff --git a/shootout/k-nucleotide/Makefile b/shootout/k-nucleotide/Makefile index ceeda7a..a37cbad 100644 --- a/shootout/k-nucleotide/Makefile +++ b/shootout/k-nucleotide/Makefile @@ -17,27 +17,28 @@ HC_OPTS += -O2 -XBangPatterns -package bytestring fasta-c : ../fasta/fasta-c.c $(CC) -std=gnu99 -O3 -fomit-frame-pointer $< -o $@ -knucleotide-input250000.txt : fasta-c +k-nucleotide.faststdin : fasta-c ./fasta-c $(FAST_OPTS) | tr -d '\r' > $@ -knucleotide-input2500000.txt : fasta-c +k-nucleotide.stdin : fasta-c ./fasta-c $(NORM_OPTS) | tr -d '\r' > $@ -knucleotide-input25000000.txt : fasta-c +k-nucleotide.slowstdin : fasta-c ./fasta-c $(SLOW_OPTS) | tr -d '\r' > $@ +# Since we only decide here what the INPUT_FILE is, it's required to first run +# `make boot` and only than `make` (otherwise `make` doesn't "see" the file and +# doesn't call `runstdtest` correctly) ifeq "$(mode)" "slow" - INPUT_FILE = knucleotide-input25000000.txt + INPUT_FILE = k-nucleotide.slowstdin else ifeq "$(mode)" "fast" - INPUT_FILE = knucleotide-input250000.txt + INPUT_FILE = k-nucleotide.faststdin else - INPUT_FILE = knucleotide-input2500000.txt + INPUT_FILE = k-nucleotide.stdin endif endif -SRC_RUNTEST_OPTS += -i $(INPUT_FILE) - -all boot :: $(INPUT_FILE) +boot :: $(INPUT_FILE) include $(TOP)/mk/target.mk diff --git a/shootout/reverse-complement/Makefile b/shootout/reverse-complement/Makefile index 19f976f..8fd7a9d 100644 --- a/shootout/reverse-complement/Makefile +++ b/shootout/reverse-complement/Makefile @@ -22,59 +22,56 @@ HC_OPTS += -O2 -XBangPatterns -funfolding-use-threshold=32 -XMagicHash \ fasta-c : ../fasta/fasta-c.c $(CC) -std=gnu99 -O3 -fomit-frame-pointer $< -o $@ -revcomp-input250000.txt : fasta-c +reverse-complement.faststdin : fasta-c ./fasta-c $(FAST_OPTS) | tr -d '\r' > $@ -revcomp-input2500000.txt : fasta-c +reverse-complement.stdin : fasta-c ./fasta-c $(NORM_OPTS) | tr -d '\r' > $@ -revcomp-input25000000.txt : fasta-c +reverse-complement.slowstdin : fasta-c ./fasta-c $(SLOW_OPTS) | tr -d '\r' > $@ +# Since we only decide here what the INPUT_FILE is, it's required to first run +# `make boot` and only than `make` (otherwise `make` doesn't "see" the file and +# doesn't call `runstdtest` correctly) ifeq "$(mode)" "slow" - INPUT_FILE = revcomp-input25000000.txt + INPUT_FILE = reverse-complement.slowstdin else ifeq "$(mode)" "fast" - INPUT_FILE = revcomp-input250000.txt + INPUT_FILE = reverse-complement.faststdin else - INPUT_FILE = revcomp-input2500000.txt + INPUT_FILE = reverse-complement.stdin endif endif -SRC_RUNTEST_OPTS += -i $(INPUT_FILE) - -all boot :: $(INPUT_FILE) - #------------------------------------------------------------------ # Create output to validate against revcomp-c : revcomp-c.o gcc $< -o $@ -pthread -reverse-complement.faststdout : revcomp-c +reverse-complement.faststdout : revcomp-c $(INPUT_FILE) ./revcomp-c < $(INPUT_FILE) > $@ -reverse-complement.stdout : revcomp-c +reverse-complement.stdout : revcomp-c $(INPUT_FILE) ./revcomp-c < $(INPUT_FILE) > $@ -reverse-complement.slowstdout : revcomp-c +reverse-complement.slowstdout : revcomp-c $(INPUT_FILE) ./revcomp-c < $(INPUT_FILE) > $@ -# Since the stdout files are created during the run the runstdtest -# script doesn't correctly pick them up, so we have to specify them -# explicitly here. +# Since we only decide here what the OUTPUT_FILE is, it's required to first run +# `make boot` and only than `make` (otherwise `make` doesn't "see" the file and +# doesn't call `runstdtest` correctly) ifeq "$(mode)" "slow" - STDOUT_FILE = reverse-complement.slowstdout + OUTPUT_FILE = reverse-complement.slowstdout else ifeq "$(mode)" "fast" - STDOUT_FILE = reverse-complement.faststdout + OUTPUT_FILE = reverse-complement.faststdout else - STDOUT_FILE = reverse-complement.stdout + OUTPUT_FILE = reverse-complement.stdout endif endif -SRC_RUNTEST_OPTS += -o1 $(STDOUT_FILE) - -all boot :: $(STDOUT_FILE) +boot :: $(INPUT_FILE) $(OUTPUT_FILE) include $(TOP)/mk/target.mk From git at git.haskell.org Wed Jun 7 23:24:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Jun 2017 23:24:07 +0000 (UTC) Subject: [commit: ghc] branch 'wip/dfeuer-less-hammer' created Message-ID: <20170607232407.072A73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/dfeuer-less-hammer Referencing: 4703c854cceb618a0ef57dafdce2add9aa865e46 From git at git.haskell.org Wed Jun 7 23:24:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Jun 2017 23:24:09 +0000 (UTC) Subject: [commit: ghc] wip/dfeuer-less-hammer: Stop forcing everything in coreBindsSize (4703c85) Message-ID: <20170607232409.B83633A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/dfeuer-less-hammer Link : http://ghc.haskell.org/trac/ghc/changeset/4703c854cceb618a0ef57dafdce2add9aa865e46/ghc >--------------------------------------------------------------- commit 4703c854cceb618a0ef57dafdce2add9aa865e46 Author: David Feuer Date: Wed Jun 7 16:20:05 2017 -0400 Stop forcing everything in coreBindsSize `coreBindsSize` forced a ton of structure to stop space leaks. Reid Barton has done some work recently to try to stop the leaks at their source instead. Memory residency remains well below the numbers Herbert posted on #13426 originally, but in some cases a ways above the ones from 8.0. I need to figure out how to get the numbers matched up to individual modules and do some profiling. Relates to #13426 Reviewers: austin, bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3606 >--------------------------------------------------------------- 4703c854cceb618a0ef57dafdce2add9aa865e46 compiler/coreSyn/CoreStats.hs | 30 ++++++++++++------------------ 1 file changed, 12 insertions(+), 18 deletions(-) diff --git a/compiler/coreSyn/CoreStats.hs b/compiler/coreSyn/CoreStats.hs index dd29be7..cb73d14 100644 --- a/compiler/coreSyn/CoreStats.hs +++ b/compiler/coreSyn/CoreStats.hs @@ -16,9 +16,8 @@ import CoreSyn import Outputable import Coercion import Var -import Type (Type, typeSize, seqType) -import Id (idType, isJoinId) -import CoreSeq (megaSeqIdInfo) +import Type (Type, typeSize) +import Id (isJoinId) import Data.List (foldl') @@ -105,29 +104,24 @@ coreBindsSize bs = sum (map bindSize bs) exprSize :: CoreExpr -> Int -- ^ A measure of the size of the expressions, strictly greater than 0 --- It also forces the expression pretty drastically as a side effect -- Counts *leaves*, not internal nodes. Types and coercions are not counted. -exprSize (Var v) = v `seq` 1 -exprSize (Lit lit) = lit `seq` 1 +exprSize (Var _) = 1 +exprSize (Lit _) = 1 exprSize (App f a) = exprSize f + exprSize a exprSize (Lam b e) = bndrSize b + exprSize e exprSize (Let b e) = bindSize b + exprSize e -exprSize (Case e b t as) = seqType t `seq` - exprSize e + bndrSize b + 1 + sum (map altSize as) -exprSize (Cast e co) = (seqCo co `seq` 1) + exprSize e +exprSize (Case e b _ as) = exprSize e + bndrSize b + 1 + sum (map altSize as) +exprSize (Cast e _) = 1 + exprSize e exprSize (Tick n e) = tickSize n + exprSize e -exprSize (Type t) = seqType t `seq` 1 -exprSize (Coercion co) = seqCo co `seq` 1 +exprSize (Type _) = 1 +exprSize (Coercion _) = 1 tickSize :: Tickish Id -> Int -tickSize (ProfNote cc _ _) = cc `seq` 1 -tickSize _ = 1 -- the rest are strict +tickSize (ProfNote _ _ _) = 1 +tickSize _ = 1 bndrSize :: Var -> Int -bndrSize b | isTyVar b = seqType (tyVarKind b) `seq` 1 - | otherwise = seqType (idType b) `seq` - megaSeqIdInfo (idInfo b) `seq` - 1 +bndrSize _ = 1 bndrsSize :: [Var] -> Int bndrsSize = sum . map bndrSize @@ -140,4 +134,4 @@ pairSize :: (Var, CoreExpr) -> Int pairSize (b,e) = bndrSize b + exprSize e altSize :: CoreAlt -> Int -altSize (c,bs,e) = c `seq` bndrsSize bs + exprSize e +altSize (_,bs,e) = bndrsSize bs + exprSize e From git at git.haskell.org Thu Jun 8 06:15:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jun 2017 06:15:40 +0000 (UTC) Subject: [commit: ghc] master: Fix slash escaping in cwrapper.c (bca56bd) Message-ID: <20170608061540.2D5153A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bca56bd040de64315564cdac4b7e943fc8a75ea0/ghc >--------------------------------------------------------------- commit bca56bd040de64315564cdac4b7e943fc8a75ea0 Author: Tamar Christina Date: Tue Jun 6 16:16:32 2017 +0100 Fix slash escaping in cwrapper.c Summary: Escape `\` in paths on Windows in `cwapper.c` when we re-output the paths. Test Plan: ./validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13666 Differential Revision: https://phabricator.haskell.org/D3628 >--------------------------------------------------------------- bca56bd040de64315564cdac4b7e943fc8a75ea0 driver/utils/cwrapper.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/driver/utils/cwrapper.c b/driver/utils/cwrapper.c index da6cec4..5a30274 100644 --- a/driver/utils/cwrapper.c +++ b/driver/utils/cwrapper.c @@ -59,7 +59,7 @@ char *flattenAndQuoteArgs(char *ptr, int argc, char *argv[]) *ptr++ = '"'; src = argv[i]; while(*src) { - if (*src == '"') { + if (*src == '"' || *src == '\\') { *ptr++ = '\\'; } *ptr++ = *src++; From git at git.haskell.org Thu Jun 8 07:38:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jun 2017 07:38:22 +0000 (UTC) Subject: [commit: ghc] master: Fix a lost-wakeup bug in BLACKHOLE handling (#13751) (5984729) Message-ID: <20170608073822.3031D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/598472908ebb08f6811b892f285490554c290ae3/ghc >--------------------------------------------------------------- commit 598472908ebb08f6811b892f285490554c290ae3 Author: Simon Marlow Date: Sat Jun 3 20:26:13 2017 +0100 Fix a lost-wakeup bug in BLACKHOLE handling (#13751) Summary: The problem occurred when * Threads A & B evaluate the same thunk * Thread A context-switches, so the thunk gets blackholed * Thread C enters the blackhole, creates a BLOCKING_QUEUE attached to the blackhole and thread A's `tso->bq` queue * Thread B updates the blackhole with a value, overwriting the BLOCKING_QUEUE * We GC, replacing A's update frame with stg_enter_checkbh * Throw an exception in A, which ignores the stg_enter_checkbh frame Now we have C blocked on A's tso->bq queue, but we forgot to check the queue because the stg_enter_checkbh frame has been thrown away by the exception. The solution and alternative designs are discussed in Note [upd-black-hole]. This also exposed a bug in the interpreter, whereby we were sometimes context-switching without calling `threadPaused()`. I've fixed this and added some Notes. Test Plan: * `cd testsuite/tests/concurrent && make slow` * validate Reviewers: niteria, bgamari, austin, erikd Reviewed By: erikd Subscribers: rwbarton, thomie GHC Trac Issues: #13751 Differential Revision: https://phabricator.haskell.org/D3630 >--------------------------------------------------------------- 598472908ebb08f6811b892f285490554c290ae3 includes/stg/MiscClosures.h | 2 - rts/HeapStackCheck.cmm | 24 ---------- rts/Interpreter.c | 10 +++++ rts/Messages.c | 4 +- rts/Schedule.c | 7 ++- rts/StgStartup.cmm | 3 ++ rts/sm/Evac.c | 64 +++++++++++++++++++++++++- rts/sm/Evac.h | 3 ++ rts/sm/Scav.c | 70 +++++++++++++++++++---------- testsuite/tests/concurrent/should_run/all.T | 1 + 10 files changed, 133 insertions(+), 55 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 598472908ebb08f6811b892f285490554c290ae3 From git at git.haskell.org Thu Jun 8 19:36:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jun 2017 19:36:20 +0000 (UTC) Subject: [commit: ghc] master: Bump nofib submodule (ffd948e) Message-ID: <20170608193620.9DA073A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ffd948e20bd23a017b59b36445e76ca9d4157534/ghc >--------------------------------------------------------------- commit ffd948e20bd23a017b59b36445e76ca9d4157534 Author: Ben Gamari Date: Thu Jun 8 14:49:02 2017 -0400 Bump nofib submodule >--------------------------------------------------------------- ffd948e20bd23a017b59b36445e76ca9d4157534 nofib | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/nofib b/nofib index c6b9143..eccf532 160000 --- a/nofib +++ b/nofib @@ -1 +1 @@ -Subproject commit c6b9143332b6171c251d2e72fb6a5484611031fb +Subproject commit eccf532410eee45f30c07f389f7029871fd603db From git at git.haskell.org Thu Jun 8 19:36:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jun 2017 19:36:17 +0000 (UTC) Subject: [commit: ghc] master: Revert "Make LLVM output robust to -dead_strip on mach-o platforms" (1c76dd8) Message-ID: <20170608193617.E5C753A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1c76dd85462c77b73c8efdefb6c959b41702ff3f/ghc >--------------------------------------------------------------- commit 1c76dd85462c77b73c8efdefb6c959b41702ff3f Author: Ben Gamari Date: Wed Jun 7 09:02:18 2017 -0400 Revert "Make LLVM output robust to -dead_strip on mach-o platforms" This reverts commit 667abf17dced8b4a4cd2dc6a291a6f244ffa031f. >--------------------------------------------------------------- 1c76dd85462c77b73c8efdefb6c959b41702ff3f compiler/llvmGen/LlvmCodeGen/Ppr.hs | 73 +------------------------------------ compiler/llvmGen/LlvmMangler.hs | 11 +++++- 2 files changed, 12 insertions(+), 72 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Ppr.hs b/compiler/llvmGen/LlvmCodeGen/Ppr.hs index 16c5518..8614084 100644 --- a/compiler/llvmGen/LlvmCodeGen/Ppr.hs +++ b/compiler/llvmGen/LlvmCodeGen/Ppr.hs @@ -21,8 +21,6 @@ import FastString import Outputable import Unique -import DynFlags (targetPlatform) - -- ---------------------------------------------------------------------------- -- * Top level -- @@ -151,75 +149,8 @@ pprLlvmCmmDecl (CmmProc mb_info entry_lbl live (ListGraph blks)) alias = LMGlobal funVar (Just $ LMBitc (LMStaticPointer defVar) (LMPointer $ LMInt 8)) - -- our beloved dead_strip preventer. - -- the idea here is to inject - -- - -- module asm "_symbol$dsp = _symbol-24" -- assuming prefix - -- of <{i64, i64, i64}> - -- module asm ".no_dead_strip _symbol$dsp" - -- - -- and thereby generating a second symbol - -- at the start of the info table, which is dead strip prevented. - -- - -- ideally, llvm should generate these for us, but as - -- things stand, this is the least hacky solution to - -- prevent dead_stripping of the prefix data, while - -- retaining dead stripping in general. - -- - -- The general layout of the above code results in the following: - -- - -- .------------. <- @$def$dsp - -- | Info Table | - -- |------------| <- @, @$def - -- | Fn Body | - -- '------------' - -- - -- Why this @ and @$def? As the textual llvm ir - -- generator is only handed typeless labels, it often does not - -- know the type of the label (e.g. function to call), until - -- the actual call happens. However, llvm requires symbol - -- lookups to be typed. Therefore we create the actual function - -- as @$def, and alias a bitcast to i8* as @. - -- Any subsequent lookup can lookup @ as i8* and - -- bitcast it to the required type once we want to call it. - -- - -- Why .no_dead_strip? Doesn't this prevent the linker from - -- -dead_strip'ing anything? Yes, it does. And we'll have to - -- live with this wart until a better solution is found that - -- ensures that all symbols that are used directly or - -- indirectly are marked used. - -- - -- This is all rather annoying. ghc 8.2 uses the infamous - -- Mangler to drop the .subsections_via_symbols directive - -- from the assembly. LLVM ingeniously emits said directive - -- unconditionally for mach-o files. To lift the need for - -- extra mangler step, we explicitly mark every symbol - -- .no_dead_strip. - -- - -- We are making a few assumptions here: - -- - the symbols end up being name _ in the final - -- assembly file. - -- - dsp <- case mb_info of - Nothing -> pure empty - Just (Statics _ statics) - | platformHasSubsectionsViaSymbols (targetPlatform dflags) -> do - infoStatics <- mapM genData statics - -- remember, the prefix_size is in bits! - let prefix_size = sum (map (llvmWidthInBits dflags . getStatType) - infoStatics) - dspName = defName `appendFS` fsLit "$dsp" - defSymbol = text "_" <> ftext defName - dspSymbol = text "_" <> ftext dspName - moduleAsm s = text "module asm" <+> doubleQuotes s - return $ text "; insert dead_strip preventer" - $+$ moduleAsm (dspSymbol <+> text "=" <+> defSymbol - <> text "-" <> int (prefix_size `div` 8)) - $+$ moduleAsm (text ".no_dead_strip" <+> dspSymbol) - $+$ text "; end dead_strip preventer" - | otherwise -> pure empty - - return (ppLlvmGlobal alias $+$ ppLlvmFunction fun' $+$ dsp, []) + + return (ppLlvmGlobal alias $+$ ppLlvmFunction fun', []) -- | The section we are putting info tables and their entry code into, should diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs index acf344f..eed13ba 100644 --- a/compiler/llvmGen/LlvmMangler.hs +++ b/compiler/llvmGen/LlvmMangler.hs @@ -47,11 +47,20 @@ type Rewrite = DynFlags -> B.ByteString -> Maybe B.ByteString -- | Rewrite a line of assembly source with the given rewrites, -- taking the first rewrite that applies. rewriteLine :: DynFlags -> [Rewrite] -> B.ByteString -> B.ByteString -rewriteLine dflags rewrites l = +rewriteLine dflags rewrites l + -- We disable .subsections_via_symbols on darwin and ios, as the llvm code + -- gen uses prefix data for the info table. This however does not prevent + -- llvm from generating .subsections_via_symbols, which in turn with + -- -dead_strip, strips the info tables, and therefore breaks ghc. + | isSubsectionsViaSymbols l = + (B.pack "## no .subsection_via_symbols for ghc. We need our info tables!") + | otherwise = case firstJust $ map (\rewrite -> rewrite dflags rest) rewrites of Nothing -> l Just rewritten -> B.concat $ [symbol, B.pack "\t", rewritten] where + isSubsectionsViaSymbols = B.isPrefixOf (B.pack ".subsections_via_symbols") + (symbol, rest) = splitLine l firstJust :: [Maybe a] -> Maybe a From git at git.haskell.org Thu Jun 8 19:36:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jun 2017 19:36:23 +0000 (UTC) Subject: [commit: ghc] master: Linker: Fix whitespace (3e8ab7c) Message-ID: <20170608193623.55EC63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3e8ab7c6820f16a6434a7dd2f6ce90bb3bef62bd/ghc >--------------------------------------------------------------- commit 3e8ab7c6820f16a6434a7dd2f6ce90bb3bef62bd Author: Ben Gamari Date: Mon Jun 5 19:43:02 2017 -0400 Linker: Fix whitespace [skip ci] >--------------------------------------------------------------- 3e8ab7c6820f16a6434a7dd2f6ce90bb3bef62bd rts/Linker.c | 32 ++++++++++++++++---------------- 1 file changed, 16 insertions(+), 16 deletions(-) diff --git a/rts/Linker.c b/rts/Linker.c index 6e710a1..3700726 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -1565,32 +1565,32 @@ int ocTryLoad (ObjectCode* oc) { } } -# if defined(OBJFORMAT_ELF) - r = ocResolve_ELF ( oc ); -# elif defined(OBJFORMAT_PEi386) - r = ocResolve_PEi386 ( oc ); -# elif defined(OBJFORMAT_MACHO) - r = ocResolve_MachO ( oc ); -# else +# if defined(OBJFORMAT_ELF) + r = ocResolve_ELF ( oc ); +# elif defined(OBJFORMAT_PEi386) + r = ocResolve_PEi386 ( oc ); +# elif defined(OBJFORMAT_MACHO) + r = ocResolve_MachO ( oc ); +# else barf("ocTryLoad: not implemented on this platform"); -# endif - if (!r) { return r; } +# endif + if (!r) { return r; } - // run init/init_array/ctors/mod_init_func + // run init/init_array/ctors/mod_init_func - loading_obj = oc; // tells foreignExportStablePtr what to do + loading_obj = oc; // tells foreignExportStablePtr what to do #if defined(OBJFORMAT_ELF) - r = ocRunInit_ELF ( oc ); + r = ocRunInit_ELF ( oc ); #elif defined(OBJFORMAT_PEi386) - r = ocRunInit_PEi386 ( oc ); + r = ocRunInit_PEi386 ( oc ); #elif defined(OBJFORMAT_MACHO) - r = ocRunInit_MachO ( oc ); + r = ocRunInit_MachO ( oc ); #else barf("ocTryLoad: initializers not implemented on this platform"); #endif - loading_obj = NULL; + loading_obj = NULL; - if (!r) { return r; } + if (!r) { return r; } oc->status = OBJECT_RESOLVED; From git at git.haskell.org Thu Jun 8 19:36:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jun 2017 19:36:26 +0000 (UTC) Subject: [commit: ghc] master: Add tcRnGetNameToInstancesIndex (56ef544) Message-ID: <20170608193626.348B23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/56ef54444b89b2332abe68ee62d88792f785f5a7/ghc >--------------------------------------------------------------- commit 56ef54444b89b2332abe68ee62d88792f785f5a7 Author: Douglas Wilson Date: Thu Jun 8 15:02:01 2017 -0400 Add tcRnGetNameToInstancesIndex This function in tcRnDriver, retrieves an index by name of all Class and Family instances in the current environment. This is to be used by haddock which currently looks up instances for each name, which looks at every instance for every lookup. Using this function instead of tcRnGetInfo, the haddock.base performance test improves by 10% Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: alexbiehl, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3624 >--------------------------------------------------------------- 56ef54444b89b2332abe68ee62d88792f785f5a7 compiler/main/GHC.hs | 41 ++++++++++++++++++++++++++++++++++++++++ compiler/typecheck/TcRnDriver.hs | 1 + 2 files changed, 42 insertions(+) diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index eda3471..ec9e271 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -1,4 +1,5 @@ {-# LANGUAGE CPP, NondecreasingIndentation, ScopedTypeVariables #-} +{-# LANGUAGE TupleSections, NamedFieldPuns #-} -- ----------------------------------------------------------------------------- -- @@ -113,6 +114,7 @@ module GHC ( getInfo, showModule, moduleIsBootOrNotObjectLinkable, + getNameToInstancesIndex, -- ** Inspecting types and kinds exprType, TcRnExprMode(..), @@ -333,9 +335,18 @@ import qualified Parser import Lexer import ApiAnnotation import qualified GHC.LanguageExtensions as LangExt +import NameEnv +import CoreFVs ( orphNamesOfFamInst ) +import FamInstEnv ( famInstEnvElts ) +import TcRnDriver +import Inst +import FamInst import FileCleanup +import Data.Foldable +import qualified Data.Map.Strict as Map import Data.Set (Set) +import qualified Data.Sequence as Seq import System.Directory ( doesFileExist ) import Data.Maybe import Data.List ( find ) @@ -1228,6 +1239,36 @@ findGlobalAnns deserialize target = withSession $ \hsc_env -> do getGRE :: GhcMonad m => m GlobalRdrEnv getGRE = withSession $ \hsc_env-> return $ ic_rn_gbl_env (hsc_IC hsc_env) +-- | Retrieve all type and family instances in the environment, indexed +-- by 'Name'. Each name's lists will contain every instance in which that name +-- is mentioned in the instance head. +getNameToInstancesIndex :: HscEnv + -> IO (Messages, Maybe (NameEnv ([ClsInst], [FamInst]))) +getNameToInstancesIndex hsc_env + = runTcInteractive hsc_env $ + do { loadUnqualIfaces hsc_env (hsc_IC hsc_env) + ; InstEnvs {ie_global, ie_local, ie_visible} <- tcGetInstEnvs + ; (pkg_fie, home_fie) <- tcGetFamInstEnvs + -- We use flip mappend to maintain the order of instances, + -- and Data.Sequence.Seq to keep flip mappend fast + ; let cls_index = Map.fromListWith (flip mappend) + [ (n, Seq.singleton ispec) + | ispec <- instEnvElts ie_local ++ instEnvElts ie_global + , instIsVisible ie_visible ispec + , n <- nameSetElemsStable $ orphNamesOfClsInst ispec + ] + ; let fam_index = Map.fromListWith (flip mappend) + [ (n, Seq.singleton fispec) + | fispec <- famInstEnvElts home_fie ++ famInstEnvElts pkg_fie + , n <- nameSetElemsStable $ orphNamesOfFamInst fispec + ] + ; return $ mkNameEnv $ + [ (nm, (toList clss, toList fams)) + | (nm, (clss, fams)) <- Map.toList $ Map.unionWith mappend + (fmap (,Seq.empty) cls_index) + (fmap (Seq.empty,) fam_index) + ] } + -- ----------------------------------------------------------------------------- {- ToDo: Move the primary logic here to compiler/main/Packages.hs diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index 4948703..4073fa1 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -35,6 +35,7 @@ module TcRnDriver ( tcRnMergeSignatures, instantiateSignature, tcRnInstantiateSignature, + loadUnqualIfaces, -- More private... badReexportedBootThing, checkBootDeclM, From git at git.haskell.org Thu Jun 8 19:36:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jun 2017 19:36:35 +0000 (UTC) Subject: [commit: ghc] master: Check target libtool (cd8f4b9) Message-ID: <20170608193635.028DE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cd8f4b9917c6fd9aa894ecafc505224e41b947fa/ghc >--------------------------------------------------------------- commit cd8f4b9917c6fd9aa894ecafc505224e41b947fa Author: Moritz Angermann Date: Thu Jun 8 14:59:20 2017 -0400 Check target libtool This will qualify the libtool with the target, e.g. arch-vendor-os-libtool, instead of simply using libtool. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: Ericson2314, ryantrinkle, rwbarton, thomie, erikd Differential Revision: https://phabricator.haskell.org/D3617 >--------------------------------------------------------------- cd8f4b9917c6fd9aa894ecafc505224e41b947fa aclocal.m4 | 9 +++++++-- configure.ac | 6 ++++++ 2 files changed, 13 insertions(+), 2 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index adc70bc..d566f83 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -491,8 +491,13 @@ AC_DEFUN([FP_SETTINGS], else SettingsWindresCommand="$Windres" fi - SettingsLibtoolCommand="libtool" - SettingsTouchCommand='touch' + SettingsTouchCommand='touch' + fi + if test -z "$LibtoolCmd" + then + SettingsLibtoolCommand="libtool" + else + SettingsLibtoolCommand="$LibtoolCmd" fi if test -z "$LlcCmd" then diff --git a/configure.ac b/configure.ac index 45b2ab3..a32e6b4 100644 --- a/configure.ac +++ b/configure.ac @@ -569,6 +569,11 @@ fi RanlibCmd="$RANLIB" RANLIB="$RanlibCmd" +dnl ** which libtool to use? +dnl -------------------------------------------------------------- +AC_CHECK_TARGET_TOOL([LIBTOOL], [libtool]) +LibtoolCmd="$LIBTOOL" +LIBTOOL="$LibtoolCmd" # Here is where we re-target which specific version of the LLVM # tools we are looking for. In the past, GHC supported a number of @@ -1250,6 +1255,7 @@ echo "\ ar : $ArCmd ld : $LdCmd nm : $NmCmd + libtool : $LibtoolCmd objdump : $ObjdumpCmd ranlib : $RanlibCmd windres : $Windres From git at git.haskell.org Thu Jun 8 19:36:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jun 2017 19:36:28 +0000 (UTC) Subject: [commit: ghc] master: [linker] fix armv7 & add aarch64 (1c83fd8) Message-ID: <20170608193628.F2C133A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1c83fd814b12754be8af211a387cec906ca198b3/ghc >--------------------------------------------------------------- commit 1c83fd814b12754be8af211a387cec906ca198b3 Author: Moritz Angermann Date: Thu Jun 8 14:58:38 2017 -0400 [linker] fix armv7 & add aarch64 This adds Global Offset Table logic, as well as PLT like logic for armv7 and aarch64; which replaces the preexisting symbolExtras logic, by placing the PLT tables next to the separtely loaded sections. This is needed to ensure that the symbol stubs are in range. Reviewers: bgamari, austin, erikd, simonmar Reviewed By: bgamari Subscribers: Ericson2314, ryantrinkle, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3448 >--------------------------------------------------------------- 1c83fd814b12754be8af211a387cec906ca198b3 rts/LinkerInternals.h | 11 +- rts/linker/CacheFlush.c | 23 +- rts/linker/Elf.c | 1026 ++++++++++++++++++++++++---------------- rts/linker/Elf.h | 2 +- rts/linker/ElfTypes.h | 5 + rts/linker/MachO.c | 134 +++--- rts/linker/SymbolExtras.c | 96 +--- rts/linker/elf_got.c | 131 +++++ rts/linker/elf_got.h | 15 + rts/linker/elf_plt.c | 92 ++++ rts/linker/elf_plt.h | 44 ++ rts/linker/elf_plt_aarch64.c | 120 +++++ rts/linker/elf_plt_aarch64.h | 12 + rts/linker/elf_plt_arm.c | 183 +++++++ rts/linker/elf_plt_arm.h | 12 + rts/linker/elf_reloc.c | 12 + rts/linker/elf_reloc.h | 13 + rts/linker/elf_reloc_aarch64.c | 330 +++++++++++++ rts/linker/elf_reloc_aarch64.h | 10 + rts/linker/elf_util.c | 9 +- rts/linker/elf_util.h | 12 +- rts/linker/util.h | 6 +- 22 files changed, 1681 insertions(+), 617 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 1c83fd814b12754be8af211a387cec906ca198b3 From git at git.haskell.org Thu Jun 8 19:36:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jun 2017 19:36:38 +0000 (UTC) Subject: [commit: ghc] master: Refactor temp files cleanup (3ee3822) Message-ID: <20170608193638.CE3633A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3ee3822ce588565e912ab6211e9d2cd545fc6ba6/ghc >--------------------------------------------------------------- commit 3ee3822ce588565e912ab6211e9d2cd545fc6ba6 Author: Douglas Wilson Date: Thu Jun 8 14:59:49 2017 -0400 Refactor temp files cleanup Remove filesToNotIntermediateClean from DynFlags, create a data type FilesToClean, and change filesToClean in DynFlags to be a FilesToClean. Modify SysTools.newTempName and the Temporary constructor of PipelineMonad.PipelineOutput to take a TempFileLifetime, which specifies whether a temp file should live until the end of GhcMonad.withSession, or until the next time cleanIntermediateTempFiles is called. These changes allow the cleaning of intermediate files in GhcMake to be much more efficient. HscTypes.hptObjs is removed as it is no longer used. A new performance test T13701 is added, which passes both with and without -keep-tmp-files. The test fails by 25% without the patch, and passes when -keep-tmp-files is added. Note that there are still at two hotspots caused by algorithms quadratic in the number of modules, however neither of them allocate. They are: * DriverPipeline.compileOne'.needsLinker * GhcMake.getModLoop DriverPipeline.compileOne'.needsLinker is changed slightly to improve the situation. I don't like adding these Types to DynFlags, but they need to be seen by Dynflags, SysTools and PipelineMonad. The alternative seems to be to create a new module. Reviewers: austin, hvr, bgamari, dfeuer, niteria, simonmar, erikd Reviewed By: simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13701 Differential Revision: https://phabricator.haskell.org/D3620 >--------------------------------------------------------------- 3ee3822ce588565e912ab6211e9d2cd545fc6ba6 compiler/ghc.cabal.in | 1 + compiler/ghc.mk | 1 + compiler/ghci/Linker.hs | 8 +- compiler/iface/MkIface.hs | 4 +- compiler/main/CodeOutput.hs | 6 +- compiler/main/DriverMkDepend.hs | 5 +- compiler/main/DriverPipeline.hs | 70 +++++---- compiler/main/DynFlags.hs | 32 +++- compiler/main/ErrUtils.hs | 21 +++ compiler/main/FileCleanup.hs | 249 ++++++++++++++++++++++++++++++++ compiler/main/GHC.hs | 3 +- compiler/main/GhcMake.hs | 81 +++++------ compiler/main/HscTypes.hs | 3 - compiler/main/PipelineMonad.hs | 3 +- compiler/main/SysTools.hs | 218 +--------------------------- ghc/GHCi/UI.hs | 2 +- testsuite/tests/perf/compiler/all.T | 11 ++ testsuite/tests/perf/compiler/genT13701 | 14 ++ 18 files changed, 427 insertions(+), 305 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 3ee3822ce588565e912ab6211e9d2cd545fc6ba6 From git at git.haskell.org Thu Jun 8 19:36:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jun 2017 19:36:32 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add performance test, Naperian (7bb2aa0) Message-ID: <20170608193632.48A5B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7bb2aa00bd93e0f3f00def586094e349e39035dd/ghc >--------------------------------------------------------------- commit 7bb2aa00bd93e0f3f00def586094e349e39035dd Author: Ben Gamari Date: Thu Jun 8 14:53:48 2017 -0400 testsuite: Add performance test, Naperian This is a module contributed by Austin Seipp which is fairly minimal (albeit requiring vector) but is still representative of contemporary Haskell. Reviewers: austin Subscribers: dfeuer, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3596 >--------------------------------------------------------------- 7bb2aa00bd93e0f3f00def586094e349e39035dd testsuite/tests/perf/compiler/Naperian.hs | 422 ++++++++++++++++++++++++++++++ testsuite/tests/perf/compiler/all.T | 9 + 2 files changed, 431 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 7bb2aa00bd93e0f3f00def586094e349e39035dd From git at git.haskell.org Thu Jun 8 19:36:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jun 2017 19:36:41 +0000 (UTC) Subject: [commit: ghc] master: Don't pass -dcore-lint to haddock in Haddock.mk (b10d3f3) Message-ID: <20170608193641.842DB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b10d3f36250d435f9f13079dd9e3ec1ecbb0017f/ghc >--------------------------------------------------------------- commit b10d3f36250d435f9f13079dd9e3ec1ecbb0017f Author: Douglas Wilson Date: Thu Jun 8 15:03:44 2017 -0400 Don't pass -dcore-lint to haddock in Haddock.mk This fixes the regressions in the haddock performance tests introduced in c9eb4385aad248118650725b7b699bb97ee21c0d. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13789 Differential Revision: https://phabricator.haskell.org/D3629 >--------------------------------------------------------------- b10d3f36250d435f9f13079dd9e3ec1ecbb0017f rules/haddock.mk | 38 ++++++++++++++++++++------------------ testsuite/tests/perf/haddock/all.T | 9 ++++++--- 2 files changed, 26 insertions(+), 21 deletions(-) diff --git a/rules/haddock.mk b/rules/haddock.mk index 3d3a83c..35748c3 100644 --- a/rules/haddock.mk +++ b/rules/haddock.mk @@ -42,6 +42,9 @@ html_$1 : $$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_FILE) $$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_DEPS = $$(foreach n,$$($1_$2_DEPS),$$($$n_HADDOCK_FILE) $$($$n_dist-install_$$(HADDOCK_WAY)_LIB)) +# We don't pass -dcore-lint to haddock because it caused a performance regression in #13789 +$1_$2_HADDOCK_GHC_OPTS = $$(foreach opt, $$(filter-out -dcore-lint,$$($1_$2_$$(HADDOCK_WAY)_ALL_HC_OPTS)),--optghc=$$(opt)) + ifeq "$$(HSCOLOUR_SRCS)" "YES" $1_$2_HADDOCK_FLAGS += --source-module=src/%{MODULE/./-}.html --source-entity=src/%{MODULE/./-}.html\#%{NAME} endif @@ -56,23 +59,23 @@ ifeq "$$(HSCOLOUR_SRCS)" "YES" "$$(ghc-cabal_INPLACE)" hscolour $1 $2 endif "$$(TOP)/$$(INPLACE_BIN)/haddock" \ - --verbosity=0 \ - --odir="$1/$2/doc/html/$$($1_PACKAGE)" \ - --no-tmp-comp-dir \ - --dump-interface=$$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_FILE) \ - --html \ - --hoogle \ - --title="$$($1_PACKAGE)-$$($1_$2_VERSION)$$(if $$(strip $$($1_$2_SYNOPSIS)),: $$(strip $$($1_$2_SYNOPSIS)),)" \ - --prologue="$1/$2/haddock-prologue.txt" \ - --optghc="-D__HADDOCK_VERSION__=$$(HADDOCK_VERSION_STRING)" \ - $$(foreach mod,$$($1_$2_HIDDEN_MODULES),--hide=$$(mod)) \ - $$(foreach pkg,$$($1_$2_DEPS),$$(if $$($$(pkg)_HADDOCK_FILE),--read-interface=../$$(pkg)$$(comma)../$$(pkg)/src/%{MODULE/./-}.html\#%{NAME}$$(comma)$$($$(pkg)_HADDOCK_FILE))) \ - $$(foreach opt,$$($1_$2_$$(HADDOCK_WAY)_ALL_HC_OPTS),--optghc=$$(opt)) \ - $$($1_$2_HADDOCK_FLAGS) $$($1_$2_HADDOCK_OPTS) \ - $$($1_$2_HS_SRCS) \ - $$($1_$2_EXTRA_HADDOCK_SRCS) \ - $$(EXTRA_HADDOCK_OPTS) \ - +RTS -t"$1/$2/haddock.t" --machine-readable + --verbosity=0 \ + --odir="$1/$2/doc/html/$$($1_PACKAGE)" \ + --no-tmp-comp-dir \ + --dump-interface=$$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_FILE) \ + --html \ + --hoogle \ + --title="$$($1_PACKAGE)-$$($1_$2_VERSION)$$(if $$(strip $$($1_$2_SYNOPSIS)),: $$(strip $$($1_$2_SYNOPSIS)),)" \ + --prologue="$1/$2/haddock-prologue.txt" \ + --optghc="-D__HADDOCK_VERSION__=$$(HADDOCK_VERSION_STRING)" \ + $$(foreach mod,$$($1_$2_HIDDEN_MODULES),--hide=$$(mod)) \ + $$(foreach pkg,$$($1_$2_DEPS),$$(if $$($$(pkg)_HADDOCK_FILE),--read-interface=../$$(pkg)$$(comma)../$$(pkg)/src/%{MODULE/./-}.html\#%{NAME}$$(comma)$$($$(pkg)_HADDOCK_FILE))) \ + $$($1_$2_HADDOCK_GHC_OPTS) \ + $$($1_$2_HADDOCK_FLAGS) $$($1_$2_HADDOCK_OPTS) \ + $$($1_$2_HS_SRCS) \ + $$($1_$2_EXTRA_HADDOCK_SRCS) \ + $$(EXTRA_HADDOCK_OPTS) \ + +RTS -t"$1/$2/haddock.t" --machine-readable # --no-tmp-comp-dir above is important: it saves a few minutes in a # validate. This flag lets Haddock use the pre-compiled object files @@ -89,4 +92,3 @@ endif # $1_$2_DO_HADDOCK $(call profEnd, haddock($1,$2)) endef - diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index 47421ce..64a6449 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), 27868466432, 5) + ,(wordsize(64), 25173968808, 5) # 2012-08-14: 5920822352 (amd64/Linux) # 2012-09-20: 5829972376 (amd64/Linux) # 2012-10-08: 5902601224 (amd64/Linux) @@ -40,6 +40,7 @@ test('haddock.base', # 2017-02-17: 38425793776 (x86_64/Linux) - Generalize kind of (->) # 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 ,(platform('i386-unknown-mingw32'), 2885173512, 5) # 2013-02-10: 3358693084 (x86/Windows) @@ -66,7 +67,7 @@ test('haddock.Cabal', [extra_files(['../../../../libraries/Cabal/Cabal/dist-install/haddock.t']), unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 22294859000, 5) + [(wordsize(64), 18753963960 , 5) # 2012-08-14: 3255435248 (amd64/Linux) # 2012-08-29: 3324606664 (amd64/Linux, new codegen) # 2012-10-08: 3373401360 (amd64/Linux) @@ -113,6 +114,7 @@ test('haddock.Cabal', # 2017-02-12: 18865432648 (amd64/Linux) - Type-indexed Typeable # 2017-05-31: 18269309128 (amd64/Linux) - Faster checkFamInstConsistency # 2017-06-05: 22294859000 (amd64/Linux) - Desugar modules compiled with -fno-code + # 2017-06-05: 18753963960 (amd64/Linux) - Don't pass on -dcore-lint in Haddock.mk ,(platform('i386-unknown-mingw32'), 3293415576, 5) # 2012-10-30: 1733638168 (x86/Windows) @@ -136,7 +138,7 @@ test('haddock.compiler', [extra_files(['../../../../compiler/stage2/haddock.t']), unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 65378619232, 10) + [(wordsize(64), 55990521024 , 10) # 2012-08-14: 26070600504 (amd64/Linux) # 2012-08-29: 26353100288 (amd64/Linux, new CG) # 2012-09-18: 26882813032 (amd64/Linux) @@ -156,6 +158,7 @@ test('haddock.compiler', # 2017-02-25: 55777283352 (amd64/Linux) Early inline patch # 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 ,(platform('i386-unknown-mingw32'), 367546388, 10) # 2012-10-30: 13773051312 (x86/Windows) From git at git.haskell.org Thu Jun 8 19:36:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jun 2017 19:36:44 +0000 (UTC) Subject: [commit: ghc] master: Correct optimization flags documentation (b2b4160) Message-ID: <20170608193644.38D603A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b2b416014e4276ebb660d85c3a612f7ca45ade78/ghc >--------------------------------------------------------------- commit b2b416014e4276ebb660d85c3a612f7ca45ade78 Author: Santiago Munin Date: Thu Jun 8 15:03:58 2017 -0400 Correct optimization flags documentation In a previous change (commit 4fd6207ec6960c429e6a1bcbe0282f625010f52a), the users guide was moved from XML to the RST format. This process introduced a typo: "No -O*-type option specified:" was changed to "-O*" (which is not correct). This change fixes it. See result in: https://prnt.sc/fh332n Fixes ticket #13756. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13756 Differential Revision: https://phabricator.haskell.org/D3631 >--------------------------------------------------------------- b2b416014e4276ebb660d85c3a612f7ca45ade78 docs/users_guide/using-optimisation.rst | 8 +++----- 1 file changed, 3 insertions(+), 5 deletions(-) diff --git a/docs/users_guide/using-optimisation.rst b/docs/users_guide/using-optimisation.rst index 1e74b71..88356df 100644 --- a/docs/users_guide/using-optimisation.rst +++ b/docs/users_guide/using-optimisation.rst @@ -45,11 +45,9 @@ optimisation to be performed, which can have an impact on how much of your program needs to be recompiled when you change something. This is one reason to stick to no-optimisation when developing code. -.. ghc-flag:: -O* - - This is taken to mean: “Please compile quickly; I'm not - over-bothered about compiled-code quality.” So, for example: - ``ghc -c Foo.hs`` +**No ``-O*``-type option specified:** This is taken to mean “Please +compile quickly; I'm not over-bothered about compiled-code quality.” +So, for example, ``ghc -c Foo.hs`` .. ghc-flag:: -O0 From git at git.haskell.org Fri Jun 9 07:22:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:22:53 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix Windows PATHs (41aa886) Message-ID: <20170609072253.EF90D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/41aa886926229ef91e4ace876e6178b411d6e9c6/ghc >--------------------------------------------------------------- commit 41aa886926229ef91e4ace876e6178b411d6e9c6 Author: Ben Gamari Date: Mon May 29 16:31:28 2017 -0400 Fix Windows PATHs >--------------------------------------------------------------- 41aa886926229ef91e4ace876e6178b411d6e9c6 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 Jun 9 07:23:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:02 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Disable non-Windows builds (acf9686) Message-ID: <20170609072302.141273A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/acf9686303e03e8e6b799d0fb536c9d7c501c6f4/ghc >--------------------------------------------------------------- commit acf9686303e03e8e6b799d0fb536c9d7c501c6f4 Author: Ben Gamari Date: Mon May 29 19:34:11 2017 -0400 Disable non-Windows builds >--------------------------------------------------------------- acf9686303e03e8e6b799d0fb536c9d7c501c6f4 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 Jun 9 07:22:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:22:56 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix testsuite (545817d) Message-ID: <20170609072256.A5C3A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/545817d5fec6746b77512b1188e6ee848e96f695/ghc >--------------------------------------------------------------- commit 545817d5fec6746b77512b1188e6ee848e96f695 Author: Ben Gamari Date: Tue May 30 12:11:16 2017 -0400 Fix testsuite >--------------------------------------------------------------- 545817d5fec6746b77512b1188e6ee848e96f695 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 Jun 9 07:22:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:22:59 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Hmm (09d920c) Message-ID: <20170609072259.5C3013A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/09d920c04ccb1e814e41e31e3f4d27a7e7235d98/ghc >--------------------------------------------------------------- commit 09d920c04ccb1e814e41e31e3f4d27a7e7235d98 Author: Ben Gamari Date: Mon May 29 16:45:16 2017 -0400 Hmm >--------------------------------------------------------------- 09d920c04ccb1e814e41e31e3f4d27a7e7235d98 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 Jun 9 07:23:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:04 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarName (38235bf) Message-ID: <20170609072304.C0D803A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/38235bfa7ad4aa20eafa19d30667c731499997fb/ghc >--------------------------------------------------------------- commit 38235bfa7ad4aa20eafa19d30667c731499997fb Author: Ben Gamari Date: Sat Jun 3 21:33:12 2017 -0400 Fix tarName >--------------------------------------------------------------- 38235bfa7ad4aa20eafa19d30667c731499997fb 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 Jun 9 07:23:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:07 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Parametrize on make command (64825ac) Message-ID: <20170609072307.771BA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/64825ac916e696540ee6a918140d0c1551fe8d09/ghc >--------------------------------------------------------------- commit 64825ac916e696540ee6a918140d0c1551fe8d09 Author: Ben Gamari Date: Mon May 29 15:44:39 2017 -0400 Parametrize on make command >--------------------------------------------------------------- 64825ac916e696540ee6a918140d0c1551fe8d09 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 Jun 9 07:23:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:10 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Move to scripted pipeline (9b92c15) Message-ID: <20170609072310.2CDD43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9b92c159c666eda636216d3e5904a45e8ec882e0/ghc >--------------------------------------------------------------- commit 9b92c159c666eda636216d3e5904a45e8ec882e0 Author: Ben Gamari Date: Wed May 17 20:52:58 2017 -0400 Move to scripted pipeline >--------------------------------------------------------------- 9b92c159c666eda636216d3e5904a45e8ec882e0 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 Jun 9 07:23:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:12 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Testing (c3eb498) Message-ID: <20170609072312.D7A753A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c3eb498bef213e4ea32c0cf5cbe1886d197e441d/ghc >--------------------------------------------------------------- commit c3eb498bef213e4ea32c0cf5cbe1886d197e441d Author: Ben Gamari Date: Fri Apr 28 09:53:13 2017 -0400 Testing >--------------------------------------------------------------- c3eb498bef213e4ea32c0cf5cbe1886d197e441d 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 Jun 9 07:23:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:15 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: No need to boot (90228f5) Message-ID: <20170609072315.9225B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/90228f5040f9fdc779656bf759d31fe504aae636/ghc >--------------------------------------------------------------- commit 90228f5040f9fdc779656bf759d31fe504aae636 Author: Ben Gamari Date: Sun Jun 4 10:54:49 2017 -0400 No need to boot >--------------------------------------------------------------- 90228f5040f9fdc779656bf759d31fe504aae636 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 Jun 9 07:23:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:18 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Introduce echo! make target (0f9d024) Message-ID: <20170609072318.539E03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0f9d0245719f1455d43a44c3bfcec72f3fad7873/ghc >--------------------------------------------------------------- commit 0f9d0245719f1455d43a44c3bfcec72f3fad7873 Author: Ben Gamari Date: Sun Jun 4 10:27:24 2017 -0400 Introduce echo! make target This is analogous to show! >--------------------------------------------------------------- 0f9d0245719f1455d43a44c3bfcec72f3fad7873 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 3fafcf0..dd9d8b6 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 Jun 9 07:23:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:21 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (633dbc8) Message-ID: <20170609072321.0C4CC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/633dbc8c3c6229cfacf7387c7e95819be546c9a6/ghc >--------------------------------------------------------------- commit 633dbc8c3c6229cfacf7387c7e95819be546c9a6 Author: Ben Gamari Date: Sun Jun 4 11:18:23 2017 -0400 Debug >--------------------------------------------------------------- 633dbc8c3c6229cfacf7387c7e95819be546c9a6 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 Jun 9 07:23:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:23 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Try adding type annotation (7fc7d2c) Message-ID: <20170609072323.C42693A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7fc7d2c8d19bca54a01b5bc389e89d85e2d59350/ghc >--------------------------------------------------------------- commit 7fc7d2c8d19bca54a01b5bc389e89d85e2d59350 Author: Ben Gamari Date: Sun Jun 4 11:26:54 2017 -0400 Try adding type annotation >--------------------------------------------------------------- 7fc7d2c8d19bca54a01b5bc389e89d85e2d59350 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 Jun 9 07:23:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:29 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Checkout (ffe09fc) Message-ID: <20170609072329.4CCB13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ffe09fcbfb5c5fcb863073c1b6f7d4e13a2d775f/ghc >--------------------------------------------------------------- commit ffe09fcbfb5c5fcb863073c1b6f7d4e13a2d775f Author: Ben Gamari Date: Thu May 18 01:19:52 2017 -0400 Checkout >--------------------------------------------------------------- ffe09fcbfb5c5fcb863073c1b6f7d4e13a2d775f 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 Jun 9 07:23:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:32 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Reenable everything else (10e8a7f) Message-ID: <20170609072332.07A6B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/10e8a7f2170b9b4f78666ca5c7352358df2753ad/ghc >--------------------------------------------------------------- commit 10e8a7f2170b9b4f78666ca5c7352358df2753ad Author: Ben Gamari Date: Mon May 29 22:45:19 2017 -0400 Reenable everything else >--------------------------------------------------------------- 10e8a7f2170b9b4f78666ca5c7352358df2753ad 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 Jun 9 07:23:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:26 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Build from source distribution (92a6c25) Message-ID: <20170609072326.96CFC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/92a6c25944827055b77d168377ab7e68bec559e9/ghc >--------------------------------------------------------------- commit 92a6c25944827055b77d168377ab7e68bec559e9 Author: Ben Gamari Date: Mon May 29 13:55:58 2017 -0400 Build from source distribution >--------------------------------------------------------------- 92a6c25944827055b77d168377ab7e68bec559e9 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 Jun 9 07:23:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:34 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (2d9e9da) Message-ID: <20170609072334.C75CC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2d9e9da84f7fe9dffde67ccfc261aeea90bb682b/ghc >--------------------------------------------------------------- commit 2d9e9da84f7fe9dffde67ccfc261aeea90bb682b Author: Ben Gamari Date: Sun Jun 4 11:32:08 2017 -0400 Debug >--------------------------------------------------------------- 2d9e9da84f7fe9dffde67ccfc261aeea90bb682b 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 Jun 9 07:23:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:37 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Handle documentation (1faec31) Message-ID: <20170609072337.7DEEC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/1faec31d052da6f7c8c5b9d642c9c7da3c8b054b/ghc >--------------------------------------------------------------- commit 1faec31d052da6f7c8c5b9d642c9c7da3c8b054b Author: Ben Gamari Date: Tue May 30 01:46:06 2017 -0400 Handle documentation >--------------------------------------------------------------- 1faec31d052da6f7c8c5b9d642c9c7da3c8b054b 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 Jun 9 07:23:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:42 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Kill debugging (7a74b14) Message-ID: <20170609072342.E817F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7a74b14176cc0b94e5a07be293f82e7b301b6c0a/ghc >--------------------------------------------------------------- commit 7a74b14176cc0b94e5a07be293f82e7b301b6c0a Author: Ben Gamari Date: Thu May 18 01:39:32 2017 -0400 Kill debugging >--------------------------------------------------------------- 7a74b14176cc0b94e5a07be293f82e7b301b6c0a 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 Jun 9 07:23:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:40 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix test (13eb65a) Message-ID: <20170609072340.39F973A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/13eb65ac2b8e63bb5a6e3c5d1809328ef18bb261/ghc >--------------------------------------------------------------- commit 13eb65ac2b8e63bb5a6e3c5d1809328ef18bb261 Author: Ben Gamari Date: Tue May 30 13:57:23 2017 -0400 Fix test >--------------------------------------------------------------- 13eb65ac2b8e63bb5a6e3c5d1809328ef18bb261 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 Jun 9 07:23:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:45 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring (6a7ca5d) Message-ID: <20170609072345.B06B23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/6a7ca5d5da45af16cafe24ebc302e681a586a132/ghc >--------------------------------------------------------------- commit 6a7ca5d5da45af16cafe24ebc302e681a586a132 Author: Ben Gamari Date: Wed May 17 20:20:55 2017 -0400 Refactoring >--------------------------------------------------------------- 6a7ca5d5da45af16cafe24ebc302e681a586a132 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 Jun 9 07:23:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:48 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Be more explicit (acc6c41) Message-ID: <20170609072348.867E63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/acc6c41ddc3d457a4d3f74a09f9232f2e9bde0fc/ghc >--------------------------------------------------------------- commit acc6c41ddc3d457a4d3f74a09f9232f2e9bde0fc Author: Ben Gamari Date: Tue May 30 16:04:31 2017 -0400 Be more explicit >--------------------------------------------------------------- acc6c41ddc3d457a4d3f74a09f9232f2e9bde0fc 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 Jun 9 07:23:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:51 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix source directory name (09eb01d) Message-ID: <20170609072351.42E313A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/09eb01d65edbe8e0924ba6b68fe669354eba2618/ghc >--------------------------------------------------------------- commit 09eb01d65edbe8e0924ba6b68fe669354eba2618 Author: Ben Gamari Date: Sun Jun 4 11:06:15 2017 -0400 Fix source directory name >--------------------------------------------------------------- 09eb01d65edbe8e0924ba6b68fe669354eba2618 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 Jun 9 07:23:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:53 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: bindist: Compress with threaded xz by default (a7e59be) Message-ID: <20170609072353.F220B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a7e59be540be766a696391c843f082d1792dfe71/ghc >--------------------------------------------------------------- commit a7e59be540be766a696391c843f082d1792dfe71 Author: Ben Gamari Date: Sun Jun 4 12:19:13 2017 -0400 bindist: Compress with threaded xz by default >--------------------------------------------------------------- a7e59be540be766a696391c843f082d1792dfe71 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 189439e..044c928 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -794,7 +794,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 Jun 9 07:23:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:56 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (a3f3e85) Message-ID: <20170609072356.AA0BB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a3f3e854717d7e037a4c61be99f68b96fac9683b/ghc >--------------------------------------------------------------- commit a3f3e854717d7e037a4c61be99f68b96fac9683b Author: Ben Gamari Date: Thu May 18 02:56:06 2017 -0400 Debug >--------------------------------------------------------------- a3f3e854717d7e037a4c61be99f68b96fac9683b 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 Jun 9 07:23:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:23:59 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix configure arguments (e2736be) Message-ID: <20170609072359.70DF13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/e2736be99598616f50100c97d18a27d1f96fb18b/ghc >--------------------------------------------------------------- commit e2736be99598616f50100c97d18a27d1f96fb18b Author: Ben Gamari Date: Mon May 29 22:55:51 2017 -0400 Fix configure arguments >--------------------------------------------------------------- e2736be99598616f50100c97d18a27d1f96fb18b 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 Jun 9 07:24:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:02 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Actually call closure (36ac630) Message-ID: <20170609072402.31A063A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/36ac630fa164577818e164c3d4c4bceeb6d208a4/ghc >--------------------------------------------------------------- commit 36ac630fa164577818e164c3d4c4bceeb6d208a4 Author: Ben Gamari Date: Sun Jun 4 01:02:20 2017 -0400 Actually call closure >--------------------------------------------------------------- 36ac630fa164577818e164c3d4c4bceeb6d208a4 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 Jun 9 07:24:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:05 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (d3a18a5) Message-ID: <20170609072405.20F903A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d3a18a529bfb8057d896f316679583bb309ccbc0/ghc >--------------------------------------------------------------- commit d3a18a529bfb8057d896f316679583bb309ccbc0 Author: Ben Gamari Date: Mon May 29 15:49:33 2017 -0400 Debug >--------------------------------------------------------------- d3a18a529bfb8057d896f316679583bb309ccbc0 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 Jun 9 07:24:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:07 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Unregisterised (0a919e9) Message-ID: <20170609072407.CCE813A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0a919e9bd4fe229861f746aa0908404405aa7afb/ghc >--------------------------------------------------------------- commit 0a919e9bd4fe229861f746aa0908404405aa7afb Author: Ben Gamari Date: Thu May 18 01:55:35 2017 -0400 Unregisterised >--------------------------------------------------------------- 0a919e9bd4fe229861f746aa0908404405aa7afb 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 Jun 9 07:24:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:10 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Hopefully fix Windows (9ccfe3c) Message-ID: <20170609072410.86F9D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9ccfe3ca10efcab880c54604ba07dc801150ba3b/ghc >--------------------------------------------------------------- commit 9ccfe3ca10efcab880c54604ba07dc801150ba3b Author: Ben Gamari Date: Mon May 29 22:33:46 2017 -0400 Hopefully fix Windows >--------------------------------------------------------------- 9ccfe3ca10efcab880c54604ba07dc801150ba3b 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 Jun 9 07:24:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:13 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debuggging (ef17038) Message-ID: <20170609072413.4D1803A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ef170380804abe1576fb19675fcc81addf60fac7/ghc >--------------------------------------------------------------- commit ef170380804abe1576fb19675fcc81addf60fac7 Author: Ben Gamari Date: Sun Jun 4 11:12:23 2017 -0400 Debuggging >--------------------------------------------------------------- ef170380804abe1576fb19675fcc81addf60fac7 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 Jun 9 07:24:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:16 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarball generation (4128b63) Message-ID: <20170609072416.099593A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/4128b63064597ecb225341d2972847af58a82ebc/ghc >--------------------------------------------------------------- commit 4128b63064597ecb225341d2972847af58a82ebc Author: Ben Gamari Date: Tue May 30 10:43:09 2017 -0400 Fix tarball generation >--------------------------------------------------------------- 4128b63064597ecb225341d2972847af58a82ebc 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 Jun 9 07:24:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:18 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Cross (986ae95) Message-ID: <20170609072418.B5A563A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/986ae958485d4d073a75e98991d93f38cfdaa468/ghc >--------------------------------------------------------------- commit 986ae958485d4d073a75e98991d93f38cfdaa468 Author: Ben Gamari Date: Thu May 18 01:00:42 2017 -0400 Cross >--------------------------------------------------------------- 986ae958485d4d073a75e98991d93f38cfdaa468 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 Jun 9 07:24:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:21 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: A bit more paranoia around directory deletion (f34254e) Message-ID: <20170609072421.764103A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/f34254e463b3e94c31b235158fe83a336aada5f4/ghc >--------------------------------------------------------------- commit f34254e463b3e94c31b235158fe83a336aada5f4 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. >--------------------------------------------------------------- f34254e463b3e94c31b235158fe83a336aada5f4 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 Jun 9 07:24:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:24 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring, add Windows, fix cross (6dc3ba5) Message-ID: <20170609072424.303FC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/6dc3ba510a2a428a32b7cb1a33316331895c11d1/ghc >--------------------------------------------------------------- commit 6dc3ba510a2a428a32b7cb1a33316331895c11d1 Author: Ben Gamari Date: Thu May 18 02:14:40 2017 -0400 Refactoring, add Windows, fix cross >--------------------------------------------------------------- 6dc3ba510a2a428a32b7cb1a33316331895c11d1 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 Jun 9 07:24:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:27 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rip out debug output (47201c9) Message-ID: <20170609072427.0968B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/47201c902060e245c1658281b432a7cb25647ec9/ghc >--------------------------------------------------------------- commit 47201c902060e245c1658281b432a7cb25647ec9 Author: Ben Gamari Date: Sun Jun 4 11:36:21 2017 -0400 Rip out debug output >--------------------------------------------------------------- 47201c902060e245c1658281b432a7cb25647ec9 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 Jun 9 07:24:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:29 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: More things (9ae5144) Message-ID: <20170609072429.B91F83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9ae5144e3930011244fec288385e377c641ab7e9/ghc >--------------------------------------------------------------- commit 9ae5144e3930011244fec288385e377c641ab7e9 Author: Ben Gamari Date: Thu May 18 01:38:55 2017 -0400 More things >--------------------------------------------------------------- 9ae5144e3930011244fec288385e377c641ab7e9 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 Jun 9 07:24:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:32 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add THREADS parameter (1c58559) Message-ID: <20170609072432.963D03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/1c58559075696ff909f2bf517821794572264c6e/ghc >--------------------------------------------------------------- commit 1c58559075696ff909f2bf517821794572264c6e Author: Ben Gamari Date: Sat May 13 11:59:37 2017 -0400 Add THREADS parameter >--------------------------------------------------------------- 1c58559075696ff909f2bf517821794572264c6e 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 Jun 9 07:24:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:35 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix documentation (ae2afd6) Message-ID: <20170609072435.489333A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ae2afd6efe2709f727dfb3cb9538f0c11adb94b3/ghc >--------------------------------------------------------------- commit ae2afd6efe2709f727dfb3cb9538f0c11adb94b3 Author: Ben Gamari Date: Tue May 30 10:45:52 2017 -0400 Fix documentation >--------------------------------------------------------------- ae2afd6efe2709f727dfb3cb9538f0c11adb94b3 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 Jun 9 07:24:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:38 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Testing simpler Jenkinsfile (e493c8d) Message-ID: <20170609072438.7BA003A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/e493c8d9a68a124a0eb0c51fb7b842656705fbaf/ghc >--------------------------------------------------------------- commit e493c8d9a68a124a0eb0c51fb7b842656705fbaf Author: Ben Gamari Date: Fri Apr 21 14:29:34 2017 -0400 Testing simpler Jenkinsfile >--------------------------------------------------------------- e493c8d9a68a124a0eb0c51fb7b842656705fbaf 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 Jun 9 07:24:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:41 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Disable large address space on FreeBSD (02b56bf) Message-ID: <20170609072441.33BC03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/02b56bfdc9e020320d9932f28c959624291663f2/ghc >--------------------------------------------------------------- commit 02b56bfdc9e020320d9932f28c959624291663f2 Author: Ben Gamari Date: Mon May 29 16:34:26 2017 -0400 Disable large address space on FreeBSD >--------------------------------------------------------------- 02b56bfdc9e020320d9932f28c959624291663f2 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 Jun 9 07:24:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:43 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Reformat (4587e07) Message-ID: <20170609072443.DFE493A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/4587e0741fa58a2d55a10f0adca94979d8ea5a44/ghc >--------------------------------------------------------------- commit 4587e0741fa58a2d55a10f0adca94979d8ea5a44 Author: Ben Gamari Date: Thu May 18 02:58:05 2017 -0400 Reformat >--------------------------------------------------------------- 4587e0741fa58a2d55a10f0adca94979d8ea5a44 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 Jun 9 07:24:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:46 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: More debugging (9417d06) Message-ID: <20170609072446.98EE13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9417d060fdda4f68a7474f137a3b7055c5366aa8/ghc >--------------------------------------------------------------- commit 9417d060fdda4f68a7474f137a3b7055c5366aa8 Author: Ben Gamari Date: Sat Jun 3 17:02:01 2017 -0400 More debugging >--------------------------------------------------------------- 9417d060fdda4f68a7474f137a3b7055c5366aa8 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 Jun 9 07:24:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:49 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Clean (b667a50) Message-ID: <20170609072449.554AB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/b667a5065b5e30408c30831f50fea38eeb41b7d2/ghc >--------------------------------------------------------------- commit b667a5065b5e30408c30831f50fea38eeb41b7d2 Author: Ben Gamari Date: Tue May 30 00:29:29 2017 -0400 Clean >--------------------------------------------------------------- b667a5065b5e30408c30831f50fea38eeb41b7d2 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 Jun 9 07:24:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:52 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Configure bindist (24e8d0a) Message-ID: <20170609072452.0C6E23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/24e8d0a6b2999cc1ba7cb0d4a6d9987e0099a1d1/ghc >--------------------------------------------------------------- commit 24e8d0a6b2999cc1ba7cb0d4a6d9987e0099a1d1 Author: Ben Gamari Date: Sun Jun 4 12:32:40 2017 -0400 Configure bindist >--------------------------------------------------------------- 24e8d0a6b2999cc1ba7cb0d4a6d9987e0099a1d1 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 Jun 9 07:24:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:54 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Don't run nofib on Windows (480e015) Message-ID: <20170609072454.B9AFA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/480e0150e08dcb9714ea213fb6344d6982649e08/ghc >--------------------------------------------------------------- commit 480e0150e08dcb9714ea213fb6344d6982649e08 Author: Ben Gamari Date: Mon May 29 16:14:11 2017 -0400 Don't run nofib on Windows >--------------------------------------------------------------- 480e0150e08dcb9714ea213fb6344d6982649e08 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 Jun 9 07:24:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:24:57 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Use archiveArtifacts instead of archive (98dd17b) Message-ID: <20170609072457.7211F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/98dd17bd42a26f98fe6721093dda551f0d7caa35/ghc >--------------------------------------------------------------- commit 98dd17bd42a26f98fe6721093dda551f0d7caa35 Author: Ben Gamari Date: Mon May 29 15:44:56 2017 -0400 Use archiveArtifacts instead of archive >--------------------------------------------------------------- 98dd17bd42a26f98fe6721093dda551f0d7caa35 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 Jun 9 07:25:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:00 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: No need to configure (07b093a) Message-ID: <20170609072500.33E6A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/07b093acac6a46f79b0a8a0ceb63a366b9acf180/ghc >--------------------------------------------------------------- commit 07b093acac6a46f79b0a8a0ceb63a366b9acf180 Author: Ben Gamari Date: Sun Jun 4 10:47:30 2017 -0400 No need to configure >--------------------------------------------------------------- 07b093acac6a46f79b0a8a0ceb63a366b9acf180 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 Jun 9 07:25:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:02 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Run jobs in parallel (e2f03e4) Message-ID: <20170609072502.E1F5C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/e2f03e46cb75dec7379247233e38e752a5d838a4/ghc >--------------------------------------------------------------- commit e2f03e46cb75dec7379247233e38e752a5d838a4 Author: Ben Gamari Date: Wed May 17 23:34:37 2017 -0400 Run jobs in parallel >--------------------------------------------------------------- e2f03e46cb75dec7379247233e38e752a5d838a4 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 Jun 9 07:25:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:05 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add nofib, bindist, and aarch64 support (76d4a7a) Message-ID: <20170609072505.9BF393A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/76d4a7a24e7c37192ca9f80475dd2607c58d297f/ghc >--------------------------------------------------------------- commit 76d4a7a24e7c37192ca9f80475dd2607c58d297f Author: Ben Gamari Date: Wed May 17 22:41:02 2017 -0400 Add nofib, bindist, and aarch64 support >--------------------------------------------------------------- 76d4a7a24e7c37192ca9f80475dd2607c58d297f 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 Jun 9 07:25:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:08 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Nailed the Windows issue (ac69b09) Message-ID: <20170609072508.548363A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ac69b09741ef647a42195d1c08619458eb502b2b/ghc >--------------------------------------------------------------- commit ac69b09741ef647a42195d1c08619458eb502b2b Author: Ben Gamari Date: Mon May 29 12:48:34 2017 -0400 Nailed the Windows issue >--------------------------------------------------------------- ac69b09741ef647a42195d1c08619458eb502b2b 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 Jun 9 07:25:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:11 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (6cde743) Message-ID: <20170609072511.0E41D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/6cde7438435591c5526915ed72fbaceb902bb1d4/ghc >--------------------------------------------------------------- commit 6cde7438435591c5526915ed72fbaceb902bb1d4 Author: Ben Gamari Date: Wed May 17 23:42:59 2017 -0400 Debug >--------------------------------------------------------------- 6cde7438435591c5526915ed72fbaceb902bb1d4 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 Jun 9 07:25:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:13 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Trim whitespace from git output (f57ddbc) Message-ID: <20170609072513.BD2C83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/f57ddbcda67a5c8cbeb8133b4f1196432a0f02e2/ghc >--------------------------------------------------------------- commit f57ddbcda67a5c8cbeb8133b4f1196432a0f02e2 Author: Ben Gamari Date: Sun Jun 4 11:00:28 2017 -0400 Trim whitespace from git output >--------------------------------------------------------------- f57ddbcda67a5c8cbeb8133b4f1196432a0f02e2 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 Jun 9 07:25:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:16 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Try again (0490128) Message-ID: <20170609072516.75BE13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0490128f16ee340b708f9924a056af8f8e75d0cf/ghc >--------------------------------------------------------------- commit 0490128f16ee340b708f9924a056af8f8e75d0cf Author: Ben Gamari Date: Mon May 29 16:42:42 2017 -0400 Try again >--------------------------------------------------------------- 0490128f16ee340b708f9924a056af8f8e75d0cf 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 Jun 9 07:25:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:19 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix JSON serialization (95d86fb) Message-ID: <20170609072519.2DFA43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/95d86fbe9875271e7a912bbdf993d83faa450de0/ghc >--------------------------------------------------------------- commit 95d86fbe9875271e7a912bbdf993d83faa450de0 Author: Ben Gamari Date: Wed May 31 10:43:24 2017 -0400 Fix JSON serialization >--------------------------------------------------------------- 95d86fbe9875271e7a912bbdf993d83faa450de0 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 Jun 9 07:25:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:21 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix missing binding (fdfc0fa) Message-ID: <20170609072521.DDE373A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/fdfc0faa0c3a5c4ef6101ed4efa6c91464b88d00/ghc >--------------------------------------------------------------- commit fdfc0faa0c3a5c4ef6101ed4efa6c91464b88d00 Author: Ben Gamari Date: Wed May 31 11:36:00 2017 -0400 Fix missing binding >--------------------------------------------------------------- fdfc0faa0c3a5c4ef6101ed4efa6c91464b88d00 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 Jun 9 07:25:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:24 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: windows (da10081) Message-ID: <20170609072524.9654A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/da1008128f8965fdb818301bf07f14e705f14fdd/ghc >--------------------------------------------------------------- commit da1008128f8965fdb818301bf07f14e705f14fdd Author: Ben Gamari Date: Thu May 18 01:55:46 2017 -0400 windows >--------------------------------------------------------------- da1008128f8965fdb818301bf07f14e705f14fdd 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 Jun 9 07:25:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:27 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarball names (9a1f9a8) Message-ID: <20170609072527.5BF753A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9a1f9a804005dda224dc82a6558827c1a9607198/ghc >--------------------------------------------------------------- commit 9a1f9a804005dda224dc82a6558827c1a9607198 Author: Ben Gamari Date: Sun Jun 4 10:34:37 2017 -0400 Fix tarball names >--------------------------------------------------------------- 9a1f9a804005dda224dc82a6558827c1a9607198 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 Jun 9 07:25:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:30 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix FreeBSD architecture (c5990c2) Message-ID: <20170609072530.18C103A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c5990c2cc7585dc740346d4903582d1669ef0abb/ghc >--------------------------------------------------------------- commit c5990c2cc7585dc740346d4903582d1669ef0abb Author: Ben Gamari Date: Mon May 29 13:55:03 2017 -0400 Fix FreeBSD architecture >--------------------------------------------------------------- c5990c2cc7585dc740346d4903582d1669ef0abb 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 Jun 9 07:25:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:32 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (3e5aae8) Message-ID: <20170609072532.D47AB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/3e5aae8df7efd4a0970d6891d3a6a0b052e78029/ghc >--------------------------------------------------------------- commit 3e5aae8df7efd4a0970d6891d3a6a0b052e78029 Author: Ben Gamari Date: Wed May 31 14:57:34 2017 -0400 Debug >--------------------------------------------------------------- 3e5aae8df7efd4a0970d6891d3a6a0b052e78029 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 Jun 9 07:25:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:35 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Clean up treatment of tests (74ddf12) Message-ID: <20170609072535.942FD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/74ddf12d6e8e730271eab233aa73f75f62ab53f7/ghc >--------------------------------------------------------------- commit 74ddf12d6e8e730271eab233aa73f75f62ab53f7 Author: Ben Gamari Date: Tue May 30 01:10:56 2017 -0400 Clean up treatment of tests >--------------------------------------------------------------- 74ddf12d6e8e730271eab233aa73f75f62ab53f7 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 Jun 9 07:25:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:38 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (ca84819) Message-ID: <20170609072538.525DB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ca8481984b671d203a6f9088bd820b8a794ee27a/ghc >--------------------------------------------------------------- commit ca8481984b671d203a6f9088bd820b8a794ee27a Author: Ben Gamari Date: Thu May 18 02:59:40 2017 -0400 Debug >--------------------------------------------------------------- ca8481984b671d203a6f9088bd820b8a794ee27a 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 Jun 9 07:25:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:41 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rework handling of Windows (208f37a) Message-ID: <20170609072541.0DCA23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/208f37a6b666944f32fdca837760bb8b665b4f7b/ghc >--------------------------------------------------------------- commit 208f37a6b666944f32fdca837760bb8b665b4f7b Author: Ben Gamari Date: Mon May 29 13:08:49 2017 -0400 Rework handling of Windows >--------------------------------------------------------------- 208f37a6b666944f32fdca837760bb8b665b4f7b 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 Jun 9 07:25:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:43 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Pass BINDIST to make test (5810450) Message-ID: <20170609072543.C507E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/58104505063db3a193c9d52b7d41592aceb3a572/ghc >--------------------------------------------------------------- commit 58104505063db3a193c9d52b7d41592aceb3a572 Author: Ben Gamari Date: Mon Jun 5 13:15:45 2017 -0400 Pass BINDIST to make test >--------------------------------------------------------------- 58104505063db3a193c9d52b7d41592aceb3a572 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 Jun 9 07:25:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:46 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Don't try to record commit of bindist (5f607c3) Message-ID: <20170609072546.7D36F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/5f607c3a31c17482bd24b5301f0944d74b91d81c/ghc >--------------------------------------------------------------- commit 5f607c3a31c17482bd24b5301f0944d74b91d81c Author: Ben Gamari Date: Mon Jun 5 15:31:26 2017 -0400 Don't try to record commit of bindist >--------------------------------------------------------------- 5f607c3a31c17482bd24b5301f0944d74b91d81c 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 Jun 9 07:25:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:49 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Use named argument list (283d4fc) Message-ID: <20170609072549.3B0083A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/283d4fc2a6b1f16d158a828a4d0432445af18f03/ghc >--------------------------------------------------------------- commit 283d4fc2a6b1f16d158a828a4d0432445af18f03 Author: Ben Gamari Date: Mon Jun 5 13:27:27 2017 -0400 Use named argument list >--------------------------------------------------------------- 283d4fc2a6b1f16d158a828a4d0432445af18f03 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 Jun 9 07:25:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:51 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rework handling of nofib (03a883a) Message-ID: <20170609072551.E734F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/03a883ad81b844e2525023bf1b35cb8874ea5d31/ghc >--------------------------------------------------------------- commit 03a883ad81b844e2525023bf1b35cb8874ea5d31 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. >--------------------------------------------------------------- 03a883ad81b844e2525023bf1b35cb8874ea5d31 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 Jun 9 07:25:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:54 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Run stage1 tests as well (38dce88) Message-ID: <20170609072554.9FE913A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/38dce88045e7d5fe9a71f00574c0698fc07329ef/ghc >--------------------------------------------------------------- commit 38dce88045e7d5fe9a71f00574c0698fc07329ef Author: Ben Gamari Date: Sun Jun 4 21:24:15 2017 -0400 Run stage1 tests as well >--------------------------------------------------------------- 38dce88045e7d5fe9a71f00574c0698fc07329ef 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 Jun 9 07:25:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 07:25:57 +0000 (UTC) Subject: [commit: ghc] wip/jenkins's head updated: Don't try to record commit of bindist (5f607c3) Message-ID: <20170609072557.B78993A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/jenkins' now includes: 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 e493c8d Testing simpler Jenkinsfile c3eb498 Testing 1c58559 Add THREADS parameter 6a7ca5d Refactoring 9b92c15 Move to scripted pipeline 76d4a7a Add nofib, bindist, and aarch64 support e2f03e4 Run jobs in parallel 6cde743 Debug 986ae95 Cross ffe09fc Checkout 9ae5144 More things 7a74b14 Kill debugging 0a919e9 Unregisterised da10081 windows 6dc3ba5 Refactoring, add Windows, fix cross a3f3e85 Debug 4587e07 Reformat ca84819 Debug ac69b09 Nailed the Windows issue 208f37a Rework handling of Windows c5990c2 Fix FreeBSD architecture 64825ac Parametrize on make command 98dd17b Use archiveArtifacts instead of archive d3a18a5 Debug 480e015 Don't run nofib on Windows 41aa886 Fix Windows PATHs 02b56bf Disable large address space on FreeBSD 0490128 Try again 09d920c Hmm acf9686 Disable non-Windows builds 9ccfe3c Hopefully fix Windows 10e8a7f Reenable everything else e2736be Fix configure arguments b667a50 Clean 74ddf12 Clean up treatment of tests 1faec31 Handle documentation 4128b63 Fix tarball generation ae2afd6 Fix documentation 545817d Fix testsuite 13eb65a Fix test acc6c41 Be more explicit 95d86fb Fix JSON serialization fdfc0fa Fix missing binding 3e5aae8 Debug 9417d06 More debugging 38235bf Fix tarName 36ac630 Actually call closure 92a6c25 Build from source distribution 0f9d024 Introduce echo! make target 9a1f9a8 Fix tarball names 07b093a No need to configure f34254e A bit more paranoia around directory deletion 90228f5 No need to boot f57ddbc Trim whitespace from git output 09eb01d Fix source directory name ef17038 Debuggging 633dbc8 Debug 7fc7d2c Try adding type annotation 2d9e9da Debug 47201c9 Rip out debug output a7e59be bindist: Compress with threaded xz by default 24e8d0a Configure bindist 38dce88 Run stage1 tests as well 5810450 Pass BINDIST to make test 283d4fc Use named argument list 03a883a Rework handling of nofib 5f607c3 Don't try to record commit of bindist From kyrab at mail.ru Fri Jun 9 08:27:31 2017 From: kyrab at mail.ru (kyra) Date: Fri, 9 Jun 2017 11:27:31 +0300 Subject: [commit: ghc] wip/jenkins: Rework handling of Windows (208f37a) In-Reply-To: <20170609072541.0DCA23A585@ghc.haskell.org> References: <20170609072541.0DCA23A585@ghc.haskell.org> Message-ID: <17188e54-a1a4-b7ef-2cd8-19a49d080997@mail.ru> Hi, for quite a while I see a lot of windows-related commits touching Jenkinsfile, but *all* of them are wrong in windows path handling. I know absolutely nothing about jenkins, but things like PATH = 'C:\\msys64\\mingw64\\bin:C:\\msys64\\home\\ben\\ghc-8.0.2-x86_64:$PATH' simply can't be correct. It's impossible to use colon *both* as a path separator and drive letter designator. You should *either* have something like PATH = 'C:\\msys64\\mingw64\\bin;C:\\msys64\\home\\ben\\ghc-8.0.2-x86_64;$PATH', using semicolon to separate path components, *or* PATH = '/c/msys64/mingw64/bin:/c/msys64/home/ben/ghc-8.0.2-x86_64:$PATH', using colon to separate path components, but getting rid of windows drive letter usage. HTH On 6/9/2017 10:25 AM, git at git.haskell.org wrote: > Repository : ssh://git at git.haskell.org/ghc > > On branch : wip/jenkins > Link : http://ghc.haskell.org/trac/ghc/changeset/208f37a6b666944f32fdca837760bb8b665b4f7b/ghc > >> --------------------------------------------------------------- > commit 208f37a6b666944f32fdca837760bb8b665b4f7b > Author: Ben Gamari > Date: Mon May 29 13:08:49 2017 -0400 > > Rework handling of Windows > > >> --------------------------------------------------------------- > 208f37a6b666944f32fdca837760bb8b665b4f7b > 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 > > _______________________________________________ > ghc-commits mailing list > ghc-commits at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-commits From git at git.haskell.org Fri Jun 9 20:13:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jun 2017 20:13:08 +0000 (UTC) Subject: [commit: ghc] branch 'wip/perf-testsuite' created Message-ID: <20170609201308.944D43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/perf-testsuite Referencing: b2b416014e4276ebb660d85c3a612f7ca45ade78 From git at git.haskell.org Mon Jun 12 14:05:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Jun 2017 14:05:40 +0000 (UTC) Subject: [commit: ghc] master: linker: Fix cast-to-uint64_t (0d94a3e) Message-ID: <20170612140540.DA6623A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0d94a3e0dc23bfcdb23b14c1af059a19e9d636ac/ghc >--------------------------------------------------------------- commit 0d94a3e0dc23bfcdb23b14c1af059a19e9d636ac Author: Ben Gamari Date: Mon Jun 12 09:31:29 2017 -0400 linker: Fix cast-to-uint64_t This broke on 32-bit platforms. >--------------------------------------------------------------- 0d94a3e0dc23bfcdb23b14c1af059a19e9d636ac rts/linker/elf_got.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/linker/elf_got.c b/rts/linker/elf_got.c index 41a7bd1..0395d16 100644 --- a/rts/linker/elf_got.c +++ b/rts/linker/elf_got.c @@ -116,7 +116,7 @@ verifyGot(ObjectCode * oc) { ASSERT((void*)(*(void**)symbol->got_addr) == (void*)symbol->addr); } - ASSERT(0 == ((uint64_t)symbol->addr & 0xffff000000000000)); + ASSERT(0 == ((uintptr_t)symbol->addr & 0xffff000000000000)); } } return EXIT_SUCCESS; From git at git.haskell.org Mon Jun 12 17:35:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Jun 2017 17:35:15 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix windows paths (6558453) Message-ID: <20170612173515.4C1F43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/6558453b3ea79e6adfc10b3f0ecc46df192a37a1/ghc >--------------------------------------------------------------- commit 6558453b3ea79e6adfc10b3f0ecc46df192a37a1 Author: Ben Gamari Date: Fri Jun 9 13:50:09 2017 -0400 Fix windows paths >--------------------------------------------------------------- 6558453b3ea79e6adfc10b3f0ecc46df192a37a1 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 Mon Jun 12 17:35:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Jun 2017 17:35:18 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Archive source distribution (eee6b4d) Message-ID: <20170612173518.1C9D33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/eee6b4d5b82f7a20a9d6f68451a967af2177eec3/ghc >--------------------------------------------------------------- commit eee6b4d5b82f7a20a9d6f68451a967af2177eec3 Author: Ben Gamari Date: Mon Jun 12 13:34:52 2017 -0400 Archive source distribution >--------------------------------------------------------------- eee6b4d5b82f7a20a9d6f68451a967af2177eec3 Jenkinsfile | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/Jenkinsfile b/Jenkinsfile index acaf373..5c20563 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' } } } From git at git.haskell.org Mon Jun 12 20:32:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Jun 2017 20:32:03 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Archive source distribution (5d49713) Message-ID: <20170612203203.41F083A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/5d49713657817cbd55a295f6cac2326c1b891799/ghc >--------------------------------------------------------------- commit 5d49713657817cbd55a295f6cac2326c1b891799 Author: Ben Gamari Date: Mon Jun 12 13:34:52 2017 -0400 Archive source distribution >--------------------------------------------------------------- 5d49713657817cbd55a295f6cac2326c1b891799 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 Mon Jun 12 20:32:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Jun 2017 20:32:05 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Ensure that carch, prefix, and ghcPath are in scope (fa44c1a) Message-ID: <20170612203205.EAAE13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/fa44c1a81260cddfe5dc65edebf41ac609ba52ba/ghc >--------------------------------------------------------------- commit fa44c1a81260cddfe5dc65edebf41ac609ba52ba Author: Ben Gamari Date: Mon Jun 12 16:31:31 2017 -0400 Ensure that carch, prefix, and ghcPath are in scope >--------------------------------------------------------------- fa44c1a81260cddfe5dc65edebf41ac609ba52ba 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 Mon Jun 12 20:52:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Jun 2017 20:52:37 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix quoting of carch (0d6ce67) Message-ID: <20170612205237.8C79D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0d6ce676501326802f2cacf6152758291f01e9c1/ghc >--------------------------------------------------------------- commit 0d6ce676501326802f2cacf6152758291f01e9c1 Author: Ben Gamari Date: Mon Jun 12 16:40:33 2017 -0400 Fix quoting of carch >--------------------------------------------------------------- 0d6ce676501326802f2cacf6152758291f01e9c1 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 Tue Jun 13 00:22:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jun 2017 00:22:56 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Document multi-line DEPRECATED pragmas (8f72608) Message-ID: <20170613002256.B18623A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8f72608953fee7ff77a6d89b00f25749261b8820/ghc >--------------------------------------------------------------- commit 8f72608953fee7ff77a6d89b00f25749261b8820 Author: Ben Gamari Date: Mon Jun 12 17:00:55 2017 -0400 users-guide: Document multi-line DEPRECATED pragmas Fixes #13791. [skip ci] Test Plan: Read it Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #13791 Differential Revision: https://phabricator.haskell.org/D3639 >--------------------------------------------------------------- 8f72608953fee7ff77a6d89b00f25749261b8820 docs/users_guide/glasgow_exts.rst | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 20312eb..e4da54e 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -12598,6 +12598,12 @@ are two ways of using these pragmas. both are in scope. If both are in scope, there is currently no way to specify one without the other (c.f. fixities :ref:`infix-tycons`). +Also note that the argument to ``DEPRECATED`` and ``WARNING`` can also be a list +of strings, in which case the strings will be presented on separate lines in the +resulting warning message, :: + + {-# DEPRECATED foo, bar ["Don't use these", "Use gar instead"] #-} + Warnings and deprecations are not reported for (a) uses within the defining module, (b) defining a method in a class instance, and (c) uses in an export list. The latter reduces spurious complaints within a From git at git.haskell.org Tue Jun 13 00:22:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jun 2017 00:22:54 +0000 (UTC) Subject: [commit: ghc] master: Fix a bug in -foptimal-applicative-do (7e0ef11) Message-ID: <20170613002254.017D23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7e0ef11324712b4ff3ac8f39259e5ecbd63c2356/ghc >--------------------------------------------------------------- commit 7e0ef11324712b4ff3ac8f39259e5ecbd63c2356 Author: Simon Marlow Date: Mon Jun 12 17:00:39 2017 -0400 Fix a bug in -foptimal-applicative-do Test Plan: validate Reviewers: bgamari, niteria, austin, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3640 >--------------------------------------------------------------- 7e0ef11324712b4ff3ac8f39259e5ecbd63c2356 compiler/rename/RnExpr.hs | 2 +- testsuite/tests/ado/ado-optimal.hs | 11 +++++++++++ testsuite/tests/ado/ado-optimal.stdout | 1 + 3 files changed, 13 insertions(+), 1 deletion(-) diff --git a/compiler/rename/RnExpr.hs b/compiler/rename/RnExpr.hs index e1a314f..2c779d2 100644 --- a/compiler/rename/RnExpr.hs +++ b/compiler/rename/RnExpr.hs @@ -1605,7 +1605,7 @@ mkStmtTreeOptimal stmts = (StmtTreeOne (stmt_arr ! hi), 1)) | left_cost < right_cost = ((left,left_cost), (StmtTreeOne (stmt_arr ! hi), 1)) - | otherwise -- left_cost > right_cost + | left_cost > right_cost = ((StmtTreeOne (stmt_arr ! lo), 1), (right,right_cost)) | otherwise = minimumBy (comparing cost) alternatives where diff --git a/testsuite/tests/ado/ado-optimal.hs b/testsuite/tests/ado/ado-optimal.hs index aab8d53..d67aa4f 100644 --- a/testsuite/tests/ado/ado-optimal.hs +++ b/testsuite/tests/ado/ado-optimal.hs @@ -18,8 +18,19 @@ test1 = do x5 <- const e (x1,x4) return (const () x5) +-- (a | c); (b | d); e +test2 :: M () +test2 = do + x1 <- a + x3 <- c + x2 <- const b x1 + x4 <- const d x3 + x5 <- const e (x1,x4) + return (const () x5) + main = mapM_ run [ test1 + , test2 ] -- Testing code, prints out the structure of a monad/applicative expression diff --git a/testsuite/tests/ado/ado-optimal.stdout b/testsuite/tests/ado/ado-optimal.stdout index 29f9856..1df5e57 100644 --- a/testsuite/tests/ado/ado-optimal.stdout +++ b/testsuite/tests/ado/ado-optimal.stdout @@ -1 +1,2 @@ ((a; b) | (c; d)); e +(a | c); ((b | d); e) From git at git.haskell.org Tue Jun 13 00:22:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jun 2017 00:22:59 +0000 (UTC) Subject: [commit: ghc] master: Improve getNameToInstancesIndex (f942f65) Message-ID: <20170613002259.6CBC23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f942f65a525dd972cd96e6ae42922b6a3ce4b2d0/ghc >--------------------------------------------------------------- commit f942f65a525dd972cd96e6ae42922b6a3ce4b2d0 Author: Douglas Wilson Date: Mon Jun 12 17:02:01 2017 -0400 Improve getNameToInstancesIndex Put it in a GhcMonad. Stop accidentally reversing the list of instances. Add a comment noting the code is mostly copied from tcRnGetInfo. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: mpickering, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3636 >--------------------------------------------------------------- f942f65a525dd972cd96e6ae42922b6a3ce4b2d0 compiler/main/GHC.hs | 18 ++++++++++-------- compiler/typecheck/TcRnDriver.hs | 8 ++++++++ 2 files changed, 18 insertions(+), 8 deletions(-) diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index ec9e271..ce779ca 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -1242,22 +1242,24 @@ getGRE = withSession $ \hsc_env-> return $ ic_rn_gbl_env (hsc_IC hsc_env) -- | Retrieve all type and family instances in the environment, indexed -- by 'Name'. Each name's lists will contain every instance in which that name -- is mentioned in the instance head. -getNameToInstancesIndex :: HscEnv - -> IO (Messages, Maybe (NameEnv ([ClsInst], [FamInst]))) -getNameToInstancesIndex hsc_env - = runTcInteractive hsc_env $ +getNameToInstancesIndex :: GhcMonad m + => m (Messages, Maybe (NameEnv ([ClsInst], [FamInst]))) +getNameToInstancesIndex = do + hsc_env <- getSession + liftIO $ runTcInteractive hsc_env $ do { loadUnqualIfaces hsc_env (hsc_IC hsc_env) ; InstEnvs {ie_global, ie_local, ie_visible} <- tcGetInstEnvs ; (pkg_fie, home_fie) <- tcGetFamInstEnvs - -- We use flip mappend to maintain the order of instances, - -- and Data.Sequence.Seq to keep flip mappend fast - ; let cls_index = Map.fromListWith (flip mappend) + -- We use Data.Sequence.Seq because we are creating left associated + -- mappends. + -- cls_index and fam_index below are adapted from TcRnDriver.lookupInsts + ; let cls_index = Map.fromListWith mappend [ (n, Seq.singleton ispec) | ispec <- instEnvElts ie_local ++ instEnvElts ie_global , instIsVisible ie_visible ispec , n <- nameSetElemsStable $ orphNamesOfClsInst ispec ] - ; let fam_index = Map.fromListWith (flip mappend) + ; let fam_index = Map.fromListWith mappend [ (n, Seq.singleton fispec) | fispec <- famInstEnvElts home_fie ++ famInstEnvElts pkg_fie , n <- nameSetElemsStable $ orphNamesOfFamInst fispec diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index 4073fa1..35f767d 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -2441,6 +2441,14 @@ tcRnGetInfo hsc_env name ; (cls_insts, fam_insts) <- lookupInsts thing ; return (thing, fixity, cls_insts, fam_insts) } + +-- Lookup all class and family instances for a type constructor. +-- +-- This function filters all instances in the type environment, so there +-- is a lot of duplicated work if it is called many times in the same +-- type environment. If this becomes a problem, the NameEnv computed +-- in GHC.getNameToInstancesIndex could be cached in TcM and both functions +-- could be changed to consult that index. lookupInsts :: TyThing -> TcM ([ClsInst],[FamInst]) lookupInsts (ATyCon tc) = do { InstEnvs { ie_global = pkg_ie, ie_local = home_ie, ie_visible = vis_mods } <- tcGetInstEnvs From git at git.haskell.org Tue Jun 13 00:23:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jun 2017 00:23:02 +0000 (UTC) Subject: [commit: ghc] master: Fix #13807 - foreign import nondeterminism (dcdc391) Message-ID: <20170613002302.EF6303A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dcdc391609d6ff902989d806266855901c051608/ghc >--------------------------------------------------------------- commit dcdc391609d6ff902989d806266855901c051608 Author: Bartosz Nitka Date: Mon Jun 12 17:02:44 2017 -0400 Fix #13807 - foreign import nondeterminism The problem was that the generated label included a freshly assigned Unique value. Test Plan: Added a new test and looked at the generated stub: ``` #include "HsFFI.h" #ifdef __cplusplus extern "C" { #endif extern HsInt zdmainzdAzdAzuzzlzzgzzg(StgStablePtr the_stableptr); extern HsInt zdmainzdAzdAzumkStringWriter(StgStablePtr the_stableptr); #ifdef __cplusplus } #endif ``` ./validate Reviewers: simonmar, austin, bgamari Reviewed By: simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13807 Differential Revision: https://phabricator.haskell.org/D3633 >--------------------------------------------------------------- dcdc391609d6ff902989d806266855901c051608 compiler/deSugar/DsForeign.hs | 13 +++++-------- testsuite/tests/determinism/T13807/A.hs | 11 +++++++++++ testsuite/tests/determinism/{determ022 => T13807}/Makefile | 2 +- .../{determ002/determ002.stdout => T13807/T13807.stdout} | 0 testsuite/tests/determinism/T13807/all.T | 1 + 5 files changed, 18 insertions(+), 9 deletions(-) diff --git a/compiler/deSugar/DsForeign.hs b/compiler/deSugar/DsForeign.hs index fb3752d..9b088b2 100644 --- a/compiler/deSugar/DsForeign.hs +++ b/compiler/deSugar/DsForeign.hs @@ -52,6 +52,7 @@ import OrdList import Pair import Util import Hooks +import Encoding import Data.Maybe import Data.List @@ -412,16 +413,12 @@ dsFExportDynamic :: Id -> CCallConv -> DsM ([Binding], SDoc, SDoc) dsFExportDynamic id co0 cconv = do - fe_id <- newSysLocalDs ty mod <- getModule dflags <- getDynFlags - let - -- hack: need to get at the name of the C stub we're about to generate. - -- TODO: There's no real need to go via String with - -- (mkFastString . zString). In fact, is there a reason to convert - -- to FastString at all now, rather than sticking with FastZString? - fe_nm = mkFastString (zString (zEncodeFS (moduleNameFS (moduleName mod))) ++ "_" ++ toCName dflags fe_id) - + let fe_nm = mkFastString $ zEncodeString + (moduleStableString mod ++ "$" ++ toCName dflags id) + -- Construct the label based on the passed id, don't use names + -- depending on Unique. See #13807 and Note [Unique Determinism]. cback <- newSysLocalDs arg_ty newStablePtrId <- dsLookupGlobalId newStablePtrName stable_ptr_tycon <- dsLookupTyCon stablePtrTyConName diff --git a/testsuite/tests/determinism/T13807/A.hs b/testsuite/tests/determinism/T13807/A.hs new file mode 100644 index 0000000..ff8a00c --- /dev/null +++ b/testsuite/tests/determinism/T13807/A.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE ForeignFunctionInterface #-} + +module A ( mkStringWriter, (<>>) ) where + +import Foreign.Ptr +import Prelude + +-- generated C wrappers used to use Unique values for the label +foreign import ccall "wrapper" mkStringWriter :: Int -> IO (Ptr Int) +-- make sure we properly z-encode the generated stubs +foreign import ccall "wrapper" (<>>) :: Int -> IO (Ptr Int) diff --git a/testsuite/tests/determinism/determ022/Makefile b/testsuite/tests/determinism/T13807/Makefile similarity index 96% copy from testsuite/tests/determinism/determ022/Makefile copy to testsuite/tests/determinism/T13807/Makefile index 1bd543e..f420abb 100644 --- a/testsuite/tests/determinism/determ022/Makefile +++ b/testsuite/tests/determinism/T13807/Makefile @@ -2,7 +2,7 @@ TOP=../../.. include $(TOP)/mk/boilerplate.mk include $(TOP)/mk/test.mk -determ022: +T13807: $(RM) A.hi A.o '$(TEST_HC)' $(TEST_HC_OPTS) -O -dinitial-unique=0 -dunique-increment=1 A.hs $(CP) A.hi A.normal.hi diff --git a/testsuite/tests/determinism/determ002/determ002.stdout b/testsuite/tests/determinism/T13807/T13807.stdout similarity index 100% copy from testsuite/tests/determinism/determ002/determ002.stdout copy to testsuite/tests/determinism/T13807/T13807.stdout diff --git a/testsuite/tests/determinism/T13807/all.T b/testsuite/tests/determinism/T13807/all.T new file mode 100644 index 0000000..465d57c --- /dev/null +++ b/testsuite/tests/determinism/T13807/all.T @@ -0,0 +1 @@ +test('T13807', [extra_files(['A.hs'])], run_command, ['$MAKE -s --no-print-directory T13807']) From git at git.haskell.org Tue Jun 13 00:23:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jun 2017 00:23:06 +0000 (UTC) Subject: [commit: ghc] master: Add perf test for #12545 (6ddb3aa) Message-ID: <20170613002306.01D7D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6ddb3aaf5265d15a422dbaeb5396c2c20acc9ff1/ghc >--------------------------------------------------------------- commit 6ddb3aaf5265d15a422dbaeb5396c2c20acc9ff1 Author: Ryan Scott Date: Mon Jun 12 17:03:13 2017 -0400 Add perf test for #12545 Commit 2b74bd9d8b4c6b20f3e8d9ada12e7db645cc3c19 did wonders for the program reported in #12545. Let's add a perf test for it to make sure it stays fast. Test Plan: make test TEST=T12545 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #12545 Differential Revision: https://phabricator.haskell.org/D3632 >--------------------------------------------------------------- 6ddb3aaf5265d15a422dbaeb5396c2c20acc9ff1 testsuite/tests/perf/compiler/T12545.hs | 49 +++++++++++++++++++++++++++ testsuite/tests/perf/compiler/T12545a.hs | 58 ++++++++++++++++++++++++++++++++ testsuite/tests/perf/compiler/all.T | 11 ++++++ 3 files changed, 118 insertions(+) diff --git a/testsuite/tests/perf/compiler/T12545.hs b/testsuite/tests/perf/compiler/T12545.hs new file mode 100644 index 0000000..0eb07a0 --- /dev/null +++ b/testsuite/tests/perf/compiler/T12545.hs @@ -0,0 +1,49 @@ +{-# LANGUAGE EmptyDataDecls #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE MultiParamTypeClasses #-} + +module T12545 where + +import T12545a + +data A + +type instance ElemsOf A = [ T1, T2, T3, T4, T5, T6, T7, T8 + , T9, T10, T11, T12, T13, T14, T15, T16 + , T17, T18, T19, T20, T21, T22, T23, T24 + , T25, T26, T27, T28, T29, T30, T31, T32 + ] + +data T1; instance ElemOf A T1 where +data T2; instance ElemOf A T2 where +data T3; instance ElemOf A T3 where +data T4; instance ElemOf A T4 where +data T5; instance ElemOf A T5 where +data T6; instance ElemOf A T6 where +data T7; instance ElemOf A T7 where +data T8; instance ElemOf A T8 where +data T9; instance ElemOf A T9 where +data T10; instance ElemOf A T10 where +data T11; instance ElemOf A T11 where +data T12; instance ElemOf A T12 where +data T13; instance ElemOf A T13 where +data T14; instance ElemOf A T14 where +data T15; instance ElemOf A T15 where +data T16; instance ElemOf A T16 where +data T17; instance ElemOf A T17 where +data T18; instance ElemOf A T18 where +data T19; instance ElemOf A T19 where +data T20; instance ElemOf A T20 where +data T21; instance ElemOf A T21 where +data T22; instance ElemOf A T22 where +data T23; instance ElemOf A T23 where +data T24; instance ElemOf A T24 where +data T25; instance ElemOf A T25 where +data T26; instance ElemOf A T26 where +data T27; instance ElemOf A T27 where +data T28; instance ElemOf A T28 where +data T29; instance ElemOf A T29 where +data T30; instance ElemOf A T30 where +data T31; instance ElemOf A T31 where +data T32; instance ElemOf A T32 where diff --git a/testsuite/tests/perf/compiler/T12545a.hs b/testsuite/tests/perf/compiler/T12545a.hs new file mode 100644 index 0000000..3002085 --- /dev/null +++ b/testsuite/tests/perf/compiler/T12545a.hs @@ -0,0 +1,58 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE ConstraintKinds #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} + +module T12545a + ( ElemWitness(..) + , ElemAt(..) + , JustElemPath + , FindElem + , IsElem + , ElemOf + , ElemsOf + ) where + +import Data.Proxy (Proxy(..)) + +data ElemPath = HeadElem + | TailElem ElemPath + +data MaybeElemPath = NotElem + | Elem ElemPath + +type family FindElem (p :: ElemPath) (a :: k) (l :: [k]) :: MaybeElemPath where + FindElem p a (a ': t) = 'Elem p + FindElem p a (b ': t) = FindElem ('TailElem p) a t + FindElem p a '[] = 'NotElem + +type family JustElemPath (p :: MaybeElemPath) :: ElemPath where + JustElemPath ('Elem p) = p + +data ElemWitness (p :: ElemPath) (a :: k) (l :: [k]) where + ElemHeadWitness :: ElemWitness 'HeadElem a (a ': t) + ElemTailWitness :: (ElemAt p a t, + FindElem 'HeadElem a (b ': t) ~ 'Elem ('TailElem p)) + => ElemWitness p a t -> ElemWitness ('TailElem p) a (b ': t) + +class (FindElem 'HeadElem a l ~ 'Elem p) => ElemAt p (a :: k) (l :: [k]) where + elemWitness :: Proxy a -> Proxy l -> ElemWitness p a l + +instance ElemAt 'HeadElem a (a ': t) where + elemWitness _ _ = ElemHeadWitness + +instance (ElemAt p a t, FindElem 'HeadElem a (b ': t) ~ 'Elem ('TailElem p)) + => ElemAt ('TailElem p) a (b ': t) where + elemWitness pa _ = ElemTailWitness (elemWitness pa (Proxy :: Proxy t)) + +type IsElem a l = ElemAt (JustElemPath (FindElem 'HeadElem a l)) a l + +class IsElem t (ElemsOf a) => ElemOf a t where + +type family ElemsOf a :: [*] diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 8ea1c72..a55df8e 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -1043,6 +1043,17 @@ test('T12234', compile, ['']) +test('T12545', + [ only_ways(['normal']), + compiler_stats_num_field('bytes allocated', + [(wordsize(64), 3538652464, 5), + # 2017-06-08 3538652464 initial + ]), + extra_clean(['T12545a.hi', 'T12545a.o']) + ], + multimod_compile, + ['T12545', '-v0'] ) + test('T13035', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', From git at git.haskell.org Tue Jun 13 00:23:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jun 2017 00:23:09 +0000 (UTC) Subject: [commit: ghc] master: Support signatures at the kind level in Template Haskell (9a3ca8d) Message-ID: <20170613002309.4AE753A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9a3ca8deb43626c2aee10eddc029880cd2c4b4da/ghc >--------------------------------------------------------------- commit 9a3ca8deb43626c2aee10eddc029880cd2c4b4da Author: Ryan Scott Date: Mon Jun 12 17:03:32 2017 -0400 Support signatures at the kind level in Template Haskell `repNonArrowKind` was missing a case for `HsKindSig`, which this commit adds. Fixes #13781. Test Plan: make test TEST=T13781 Reviewers: goldfire, austin, bgamari Reviewed By: goldfire Subscribers: rwbarton, thomie GHC Trac Issues: #13781 Differential Revision: https://phabricator.haskell.org/D3627 >--------------------------------------------------------------- 9a3ca8deb43626c2aee10eddc029880cd2c4b4da compiler/deSugar/DsMeta.hs | 13 +++++++++++++ compiler/prelude/THNames.hs | 32 +++++++++++++++++++------------- testsuite/tests/th/T13781.hs | 10 ++++++++++ testsuite/tests/th/all.T | 1 + 4 files changed, 43 insertions(+), 13 deletions(-) diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs index f7f2fd5..d23ac38 100644 --- a/compiler/deSugar/DsMeta.hs +++ b/compiler/deSugar/DsMeta.hs @@ -1069,6 +1069,12 @@ repTyLit (HsStrTy _ s) = do { s' <- mkStringExprFS s -- represent a kind -- +-- It would be great to scrap this function in favor of repLTy, since Types +-- and Kinds are the same things. We have not done so yet for engineering +-- reasons, as repLTy returns a monadic TypeQ, whereas repLKind returns a pure +-- Kind, so in order to replace repLKind with repLTy, we'd need to go through +-- and purify repLTy and every monadic function it calls. This is the subject +-- GHC Trac #11785. repLKind :: LHsKind GhcRn -> DsM (Core TH.Kind) repLKind ki = do { let (kis, ki') = splitHsFunType ki @@ -1109,6 +1115,10 @@ repNonArrowKind (HsTupleTy _ ks) = do { ks' <- mapM repLKind ks ; kcon <- repKTuple (length ks) ; repKApps kcon ks' } +repNonArrowKind (HsKindSig k sort) = do { k' <- repLKind k + ; sort' <- repLKind sort + ; repKSig k' sort' + } repNonArrowKind k = notHandled "Exotic form of kind" (ppr k) repRole :: Located (Maybe Role) -> DsM (Core TH.Role) @@ -2351,6 +2361,9 @@ repKStar = rep2 starKName [] repKConstraint :: DsM (Core TH.Kind) repKConstraint = rep2 constraintKName [] +repKSig :: Core TH.Kind -> Core TH.Kind -> DsM (Core TH.Kind) +repKSig (MkC k) (MkC sort) = rep2 sigTDataConName [k, sort] + ---------------------------------------------------------- -- Type family result signature diff --git a/compiler/prelude/THNames.hs b/compiler/prelude/THNames.hs index 1b9e624..9502e9e 100644 --- a/compiler/prelude/THNames.hs +++ b/compiler/prelude/THNames.hs @@ -94,7 +94,7 @@ templateHaskellNames = [ -- Type forallTName, varTName, conTName, appTName, equalityTName, tupleTName, unboxedTupleTName, unboxedSumTName, - arrowTName, listTName, sigTName, litTName, + arrowTName, listTName, sigTName, sigTDataConName, litTName, promotedTName, promotedTupleTName, promotedNilTName, promotedConsTName, wildCardTName, -- TyLit @@ -428,9 +428,10 @@ recordPatSynName = libFun (fsLit "recordPatSyn") recordPatSynIdKey -- data Type = ... forallTName, varTName, conTName, tupleTName, unboxedTupleTName, - unboxedSumTName, arrowTName, listTName, appTName, sigTName, equalityTName, - litTName, promotedTName, promotedTupleTName, promotedNilTName, - promotedConsTName, wildCardTName :: Name + unboxedSumTName, arrowTName, listTName, appTName, sigTName, + sigTDataConName, equalityTName, litTName, promotedTName, + promotedTupleTName, promotedNilTName, promotedConsTName, + wildCardTName :: Name forallTName = libFun (fsLit "forallT") forallTIdKey varTName = libFun (fsLit "varT") varTIdKey conTName = libFun (fsLit "conT") conTIdKey @@ -441,6 +442,9 @@ arrowTName = libFun (fsLit "arrowT") arrowTIdKey listTName = libFun (fsLit "listT") listTIdKey appTName = libFun (fsLit "appT") appTIdKey sigTName = libFun (fsLit "sigT") sigTIdKey +-- Yes, we need names for both the monadic sigT as well as the pure SigT. Why? +-- Refer to the documentation for repLKind in DsMeta. +sigTDataConName = thCon (fsLit "SigT") sigTDataConKey equalityTName = libFun (fsLit "equalityT") equalityTIdKey litTName = libFun (fsLit "litT") litTIdKey promotedTName = libFun (fsLit "promotedT") promotedTIdKey @@ -947,8 +951,9 @@ recordPatSynIdKey = mkPreludeMiscIdUnique 372 -- data Type = ... forallTIdKey, varTIdKey, conTIdKey, tupleTIdKey, unboxedTupleTIdKey, unboxedSumTIdKey, arrowTIdKey, listTIdKey, appTIdKey, sigTIdKey, - equalityTIdKey, litTIdKey, promotedTIdKey, promotedTupleTIdKey, - promotedNilTIdKey, promotedConsTIdKey, wildCardTIdKey :: Unique + sigTDataConKey, equalityTIdKey, litTIdKey, promotedTIdKey, + promotedTupleTIdKey, promotedNilTIdKey, promotedConsTIdKey, + wildCardTIdKey :: Unique forallTIdKey = mkPreludeMiscIdUnique 381 varTIdKey = mkPreludeMiscIdUnique 382 conTIdKey = mkPreludeMiscIdUnique 383 @@ -959,13 +964,14 @@ arrowTIdKey = mkPreludeMiscIdUnique 387 listTIdKey = mkPreludeMiscIdUnique 388 appTIdKey = mkPreludeMiscIdUnique 389 sigTIdKey = mkPreludeMiscIdUnique 390 -equalityTIdKey = mkPreludeMiscIdUnique 391 -litTIdKey = mkPreludeMiscIdUnique 392 -promotedTIdKey = mkPreludeMiscIdUnique 393 -promotedTupleTIdKey = mkPreludeMiscIdUnique 394 -promotedNilTIdKey = mkPreludeMiscIdUnique 395 -promotedConsTIdKey = mkPreludeMiscIdUnique 396 -wildCardTIdKey = mkPreludeMiscIdUnique 397 +sigTDataConKey = mkPreludeMiscIdUnique 391 +equalityTIdKey = mkPreludeMiscIdUnique 392 +litTIdKey = mkPreludeMiscIdUnique 393 +promotedTIdKey = mkPreludeMiscIdUnique 394 +promotedTupleTIdKey = mkPreludeMiscIdUnique 395 +promotedNilTIdKey = mkPreludeMiscIdUnique 396 +promotedConsTIdKey = mkPreludeMiscIdUnique 397 +wildCardTIdKey = mkPreludeMiscIdUnique 398 -- data TyLit = ... numTyLitIdKey, strTyLitIdKey :: Unique diff --git a/testsuite/tests/th/T13781.hs b/testsuite/tests/th/T13781.hs new file mode 100644 index 0000000..7498f56 --- /dev/null +++ b/testsuite/tests/th/T13781.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE TypeInType #-} +module T13781 where + +import Data.Kind +import Data.Proxy + +$([d| f :: Proxy (a :: (k :: Type)) + f = Proxy + |]) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 40e3b17..e0985f1 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -386,3 +386,4 @@ test('T13473', normal, multimod_compile_and_run, test('T13587', expect_broken(13587), compile_and_run, ['-v0']) test('T13618', normal, compile_and_run, ['-v0']) test('T13642', normal, compile_fail, ['-v0']) +test('T13781', normal, compile, ['-v0']) From git at git.haskell.org Tue Jun 13 00:23:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jun 2017 00:23:11 +0000 (UTC) Subject: [commit: ghc] master: Stop forcing everything in coreBindsSize (2088d0b) Message-ID: <20170613002312.001093A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2088d0be17dccfa91a4759bdbb20faae77c8dbed/ghc >--------------------------------------------------------------- commit 2088d0be17dccfa91a4759bdbb20faae77c8dbed Author: David Feuer Date: Mon Jun 12 17:03:52 2017 -0400 Stop forcing everything in coreBindsSize `coreBindsSize` forced a ton of structure to stop space leaks. Reid Barton has done some work recently to try to stop the leaks at their source instead. Memory residency remains well below the numbers Herbert posted on #13426 originally, but in some cases a ways above the ones from 8.0. I need to figure out how to get the numbers matched up to individual modules and do some profiling. Relates to #13426 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3606 >--------------------------------------------------------------- 2088d0be17dccfa91a4759bdbb20faae77c8dbed compiler/coreSyn/CoreStats.hs | 30 ++++++++++++------------------ 1 file changed, 12 insertions(+), 18 deletions(-) diff --git a/compiler/coreSyn/CoreStats.hs b/compiler/coreSyn/CoreStats.hs index dd29be7..cb73d14 100644 --- a/compiler/coreSyn/CoreStats.hs +++ b/compiler/coreSyn/CoreStats.hs @@ -16,9 +16,8 @@ import CoreSyn import Outputable import Coercion import Var -import Type (Type, typeSize, seqType) -import Id (idType, isJoinId) -import CoreSeq (megaSeqIdInfo) +import Type (Type, typeSize) +import Id (isJoinId) import Data.List (foldl') @@ -105,29 +104,24 @@ coreBindsSize bs = sum (map bindSize bs) exprSize :: CoreExpr -> Int -- ^ A measure of the size of the expressions, strictly greater than 0 --- It also forces the expression pretty drastically as a side effect -- Counts *leaves*, not internal nodes. Types and coercions are not counted. -exprSize (Var v) = v `seq` 1 -exprSize (Lit lit) = lit `seq` 1 +exprSize (Var _) = 1 +exprSize (Lit _) = 1 exprSize (App f a) = exprSize f + exprSize a exprSize (Lam b e) = bndrSize b + exprSize e exprSize (Let b e) = bindSize b + exprSize e -exprSize (Case e b t as) = seqType t `seq` - exprSize e + bndrSize b + 1 + sum (map altSize as) -exprSize (Cast e co) = (seqCo co `seq` 1) + exprSize e +exprSize (Case e b _ as) = exprSize e + bndrSize b + 1 + sum (map altSize as) +exprSize (Cast e _) = 1 + exprSize e exprSize (Tick n e) = tickSize n + exprSize e -exprSize (Type t) = seqType t `seq` 1 -exprSize (Coercion co) = seqCo co `seq` 1 +exprSize (Type _) = 1 +exprSize (Coercion _) = 1 tickSize :: Tickish Id -> Int -tickSize (ProfNote cc _ _) = cc `seq` 1 -tickSize _ = 1 -- the rest are strict +tickSize (ProfNote _ _ _) = 1 +tickSize _ = 1 bndrSize :: Var -> Int -bndrSize b | isTyVar b = seqType (tyVarKind b) `seq` 1 - | otherwise = seqType (idType b) `seq` - megaSeqIdInfo (idInfo b) `seq` - 1 +bndrSize _ = 1 bndrsSize :: [Var] -> Int bndrsSize = sum . map bndrSize @@ -140,4 +134,4 @@ pairSize :: (Var, CoreExpr) -> Int pairSize (b,e) = bndrSize b + exprSize e altSize :: CoreAlt -> Int -altSize (c,bs,e) = c `seq` bndrsSize bs + exprSize e +altSize (_,bs,e) = bndrsSize bs + exprSize e From git at git.haskell.org Tue Jun 13 00:23:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jun 2017 00:23:15 +0000 (UTC) Subject: [commit: ghc] master: Make -w less aggressive (Trac #12056) (af9612b) Message-ID: <20170613002315.AC09A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/af9612bf862daaa99384eefa3059054053ecbee8/ghc >--------------------------------------------------------------- commit af9612bf862daaa99384eefa3059054053ecbee8 Author: Sean Gillespie Date: Mon Jun 12 17:04:05 2017 -0400 Make -w less aggressive (Trac #12056) Previously -w combined with -Wunrecognised-warning-flags would not report unrecognized flags. Reviewers: austin, bgamari, dfeuer Reviewed By: bgamari Subscribers: dfeuer, rwbarton, thomie GHC Trac Issues: #12056 Differential Revision: https://phabricator.haskell.org/D3581 >--------------------------------------------------------------- af9612bf862daaa99384eefa3059054053ecbee8 compiler/main/CmdLineParser.hs | 46 ++++++++++++++++++---- compiler/main/DynFlags.hs | 32 ++++++++------- compiler/main/GHC.hs | 7 ++-- compiler/main/HscTypes.hs | 33 ++++++++++------ ghc/Main.hs | 8 ++-- testsuite/tests/driver/{T11429a.hs => T12056a.hs} | 0 .../tests/driver/T12056a.stderr | 0 testsuite/tests/driver/{T11429a.hs => T12056b.hs} | 0 testsuite/tests/driver/T12056b.stderr | 2 + testsuite/tests/driver/{T11429a.hs => T12056c.hs} | 0 .../T3787.stderr => driver/T12056c.stderr} | 4 +- testsuite/tests/driver/all.T | 5 +++ testsuite/tests/safeHaskell/check/pkg01/Makefile | 2 +- utils/ghctags/Main.hs | 3 +- 14 files changed, 99 insertions(+), 43 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc af9612bf862daaa99384eefa3059054053ecbee8 From git at git.haskell.org Tue Jun 13 02:25:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jun 2017 02:25:26 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix binding name (bd92eed) Message-ID: <20170613022526.273313A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/bd92eed3d1ed899e5e4d9d057b2794120023b4e0/ghc >--------------------------------------------------------------- commit bd92eed3d1ed899e5e4d9d057b2794120023b4e0 Author: Ben Gamari Date: Mon Jun 12 22:25:11 2017 -0400 Fix binding name >--------------------------------------------------------------- bd92eed3d1ed899e5e4d9d057b2794120023b4e0 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 Tue Jun 13 10:06:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jun 2017 10:06:10 +0000 (UTC) Subject: [commit: ghc] master: Typos [ci skip] (0058a34) Message-ID: <20170613100610.0738A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0058a3490fc3908e00ba65e700fecc54b786e28a/ghc >--------------------------------------------------------------- commit 0058a3490fc3908e00ba65e700fecc54b786e28a Author: Gabor Greif Date: Fri Jun 9 15:55:41 2017 +0200 Typos [ci skip] >--------------------------------------------------------------- 0058a3490fc3908e00ba65e700fecc54b786e28a compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 2 +- compiler/specialise/Specialise.hs | 2 +- rts/linker/Elf.c | 2 +- rts/linker/ElfTypes.h | 2 +- rts/sm/HeapAlloc.h | 2 +- 5 files changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 0381324..bf84782 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -506,7 +506,7 @@ genCallExtract :: ForeignTarget -- ^ PrimOp -> Width -- ^ Width of the operands. -> (CmmActual, CmmActual) -- ^ Actual arguments. - -> (LlvmType, LlvmType) -- ^ LLLVM types of the returned sturct. + -> (LlvmType, LlvmType) -- ^ LLVM types of the returned struct. -> LlvmM (LlvmVar, LlvmVar, StmtData) genCallExtract target@(PrimTarget op) w (argA, argB) (llvmTypeA, llvmTypeB) = do let width = widthToLlvmInt w diff --git a/compiler/specialise/Specialise.hs b/compiler/specialise/Specialise.hs index a1ee94c..869da64 100644 --- a/compiler/specialise/Specialise.hs +++ b/compiler/specialise/Specialise.hs @@ -1854,7 +1854,7 @@ We gather the call info for (f @T $df), and we don't want to drop it when we come across the binding for $df. So we add $df to the floats and continue. But then we have to add $c== to the floats, and so on. These all float above the binding for 'f', and and now we can -successfullly specialise 'f'. +successfully specialise 'f'. So the DictBinds in (ud_binds :: Bag DictBind) may contain non-dictionary bindings too. diff --git a/rts/linker/Elf.c b/rts/linker/Elf.c index 2ae731b..e81b97a 100644 --- a/rts/linker/Elf.c +++ b/rts/linker/Elf.c @@ -1118,7 +1118,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, case COMPAT_R_ARM_CALL: case COMPAT_R_ARM_JUMP24: { - // N.B. LLVM's LLD linker's relocation implement is a fantastic + // N.B. LLVM's LLD linker's relocation implementation is a fantastic // resource StgWord32 *word = (StgWord32 *)P; StgInt32 imm = (*word & ((1<<24)-1)) << 2; diff --git a/rts/linker/ElfTypes.h b/rts/linker/ElfTypes.h index 9e2e42f..852d82a 100644 --- a/rts/linker/ElfTypes.h +++ b/rts/linker/ElfTypes.h @@ -149,7 +149,7 @@ struct _Stub { void * target; /* flags can hold architecture specific information they are used during * lookup of stubs as well. Thus two stubs for the same target with - * different flags are considerd unequal. + * different flags are considered unequal. */ uint8_t flags; struct _Stub * next; diff --git a/rts/sm/HeapAlloc.h b/rts/sm/HeapAlloc.h index 197317f..1d9d237 100644 --- a/rts/sm/HeapAlloc.h +++ b/rts/sm/HeapAlloc.h @@ -132,7 +132,7 @@ extern StgWord8 mblock_map[]; #if defined(x86_64_HOST_ARCH) // 32bits are enough for 'entry' as modern amd64 boxes have -// only 48bit sized virtual addres. +// only 48bit sized virtual address. typedef StgWord32 MbcCacheLine; #else // 32bits is not enough here as some arches (like ia64) use From git at git.haskell.org Tue Jun 13 13:43:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jun 2017 13:43:33 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix GHC path (5f0d7e8) Message-ID: <20170613134333.178CE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/5f0d7e8c97d907cbfeacb5c15fda816322f46ea7/ghc >--------------------------------------------------------------- commit 5f0d7e8c97d907cbfeacb5c15fda816322f46ea7 Author: Ben Gamari Date: Tue Jun 13 00:44:15 2017 -0400 Fix GHC path >--------------------------------------------------------------- 5f0d7e8c97d907cbfeacb5c15fda816322f46ea7 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 Wed Jun 14 10:15:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jun 2017 10:15:54 +0000 (UTC) Subject: [commit: ghc] master: Fix Haddock markup (ece39c3) Message-ID: <20170614101554.6E48C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ece39c34b7846647441251fe72654f70cdf4a9a4/ghc >--------------------------------------------------------------- commit ece39c34b7846647441251fe72654f70cdf4a9a4 Author: Gabor Greif Date: Wed Jun 14 12:14:54 2017 +0200 Fix Haddock markup >--------------------------------------------------------------- ece39c34b7846647441251fe72654f70cdf4a9a4 libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 2b99a7a..a6ead31 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -1941,7 +1941,7 @@ data Type = ForallT [TyVarBndr] Cxt Type -- ^ @forall \. \ -> \ Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/430137c45420153dafbd448b4d509f893fe675f4/ghc >--------------------------------------------------------------- commit 430137c45420153dafbd448b4d509f893fe675f4 Author: Bartosz Nitka Date: Wed Jun 14 08:51:43 2017 -0700 Add mapMG to allow making ModuleGraph abstract Currently GHC exposes the internal details of `ModuleGraph` which inhibits making `ModuleGraph` support faster lookups. Haddock relies on the internal representation by using `map` on `ModuleGraph`. See also https://github.com/haskell/haddock/issues/635 Adding `mapMG` should allow us to make `ModuleGraph` abstract. Test Plan: ./validate Reviewers: simonmar, austin, bgamari, alexbiehl Reviewed By: bgamari, alexbiehl Subscribers: alexbiehl, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3645 >--------------------------------------------------------------- 430137c45420153dafbd448b4d509f893fe675f4 compiler/main/GHC.hs | 5 +++-- compiler/main/HscTypes.hs | 5 ++++- 2 files changed, 7 insertions(+), 3 deletions(-) diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index d58f3e9..2102009 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -59,7 +59,8 @@ module GHC ( compileToCoreModule, compileToCoreSimplified, -- * Inspecting the module structure of the program - ModuleGraph, ModSummary(..), ms_mod_name, ModLocation(..), + ModuleGraph, emptyMG, mapMG, + ModSummary(..), ms_mod_name, ModLocation(..), getModSummary, getModuleGraph, isLoaded, @@ -630,7 +631,7 @@ setProgramDynFlags_ invalidate_needed dflags = do -- invalidateModSummaryCache :: GhcMonad m => m () invalidateModSummaryCache = - modifySession $ \h -> h { hsc_mod_graph = map inval (hsc_mod_graph h) } + modifySession $ \h -> h { hsc_mod_graph = mapMG inval (hsc_mod_graph h) } where inval ms = ms { ms_hs_date = addUTCTime (-1) (ms_hs_date ms) } diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs index 369a190..fa9c18a 100644 --- a/compiler/main/HscTypes.hs +++ b/compiler/main/HscTypes.hs @@ -12,7 +12,7 @@ module HscTypes ( HscEnv(..), hscEPS, FinderCache, FindResult(..), InstalledFindResult(..), Target(..), TargetId(..), pprTarget, pprTargetId, - ModuleGraph, emptyMG, + ModuleGraph, emptyMG, mapMG, HscStatus(..), IServ(..), @@ -2611,6 +2611,9 @@ type ModuleGraph = [ModSummary] emptyMG :: ModuleGraph emptyMG = [] +mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph +mapMG = map + -- | A single node in a 'ModuleGraph'. The nodes of the module graph -- are one of: -- From git at git.haskell.org Wed Jun 14 17:13:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jun 2017 17:13:14 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Show location of stage0 compiler (4eb46f7) Message-ID: <20170614171314.949083A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/4eb46f77d130e3f477e5e8b6dbcad943b5d177ae/ghc >--------------------------------------------------------------- commit 4eb46f77d130e3f477e5e8b6dbcad943b5d177ae Author: Ben Gamari Date: Tue Jun 13 16:10:23 2017 -0400 Show location of stage0 compiler >--------------------------------------------------------------- 4eb46f77d130e3f477e5e8b6dbcad943b5d177ae 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 Wed Jun 14 20:52:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jun 2017 20:52:40 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: testsuite: Mark T13708 as broken (f88bd0f) Message-ID: <20170614205240.37CE33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/f88bd0f217cbcad154c1c1d781c1b4d011282693/ghc >--------------------------------------------------------------- commit f88bd0f217cbcad154c1c1d781c1b4d011282693 Author: Ben Gamari Date: Wed Jun 14 14:00:31 2017 -0400 testsuite: Mark T13708 as broken Despite passing on master, it still seems there are numberous places in the tree where TyVars are treated as Ids. One such place is DmdAnal.dmdAnal', as mentioned in ticket:13708#comment:13. >--------------------------------------------------------------- f88bd0f217cbcad154c1c1d781c1b4d011282693 testsuite/tests/simplCore/should_compile/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index 83aab1e..a3ea645 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -260,4 +260,4 @@ test('T13468', run_command, ['$MAKE -s --no-print-directory T13468']) test('T13658', normal, compile, ['-dcore-lint']) -test('T13708', normal, compile, ['']) +test('T13708', expect_broken(13708), compile, ['']) From git at git.haskell.org Wed Jun 14 20:52:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jun 2017 20:52:42 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Add a flag reference entry for -XTypeInType (1021de1) Message-ID: <20170614205242.E09BC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/1021de1d37621b1c97e34ec6b139e05248ead668/ghc >--------------------------------------------------------------- commit 1021de1d37621b1c97e34ec6b139e05248ead668 Author: Ryan Scott Date: Fri Jun 2 11:48:44 2017 -0400 Add a flag reference entry for -XTypeInType Test Plan: Read it Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13762 Differential Revision: https://phabricator.haskell.org/D3614 (cherry picked from commit d0fb0df349d0e51b2b3f7980a8b1eca80051d67f) >--------------------------------------------------------------- 1021de1d37621b1c97e34ec6b139e05248ead668 utils/mkUserGuidePart/Options/Language.hs | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/utils/mkUserGuidePart/Options/Language.hs b/utils/mkUserGuidePart/Options/Language.hs index 11adca1..0207aa4 100644 --- a/utils/mkUserGuidePart/Options/Language.hs +++ b/utils/mkUserGuidePart/Options/Language.hs @@ -709,6 +709,17 @@ languageOptions = , flagReverse = "-XNoTypeFamilies" , flagSince = "6.8.1" } + , flag { flagName = "-XTypeInType" + , flagDescription = + "Allow :ref:`kinds to be used as types `, " ++ + "including explicit kind variable quantification, higher-rank "++ + "kinds, kind synonyms, and kind families. "++ + "Implies :ghc-flag:`-XDataKinds`, :ghc-flag:`-XKindSignatures`, " ++ + "and :ghc-flag:`-XPolyKinds`." + , flagType = DynamicFlag + , flagReverse = "-XNoTypeInType" + , flagSince = "8.0.1" + } , flag { flagName = "-XTypeOperators" , flagDescription = "Enable :ref:`type operators `. "++ From git at git.haskell.org Wed Jun 14 20:52:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jun 2017 20:52:48 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Correct optimization flags documentation (5eb4a35) Message-ID: <20170614205248.564BF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/5eb4a35bcc6743fce33eaf42b15d17e48936e41f/ghc >--------------------------------------------------------------- commit 5eb4a35bcc6743fce33eaf42b15d17e48936e41f Author: Santiago Munin Date: Thu Jun 8 15:03:58 2017 -0400 Correct optimization flags documentation In a previous change (commit 4fd6207ec6960c429e6a1bcbe0282f625010f52a), the users guide was moved from XML to the RST format. This process introduced a typo: "No -O*-type option specified:" was changed to "-O*" (which is not correct). This change fixes it. See result in: https://prnt.sc/fh332n Fixes ticket #13756. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13756 Differential Revision: https://phabricator.haskell.org/D3631 (cherry picked from commit b2b416014e4276ebb660d85c3a612f7ca45ade78) >--------------------------------------------------------------- 5eb4a35bcc6743fce33eaf42b15d17e48936e41f docs/users_guide/using-optimisation.rst | 8 +++----- 1 file changed, 3 insertions(+), 5 deletions(-) diff --git a/docs/users_guide/using-optimisation.rst b/docs/users_guide/using-optimisation.rst index dbdd957..e2e7887 100644 --- a/docs/users_guide/using-optimisation.rst +++ b/docs/users_guide/using-optimisation.rst @@ -45,11 +45,9 @@ optimisation to be performed, which can have an impact on how much of your program needs to be recompiled when you change something. This is one reason to stick to no-optimisation when developing code. -.. ghc-flag:: -O* - - This is taken to mean: “Please compile quickly; I'm not - over-bothered about compiled-code quality.” So, for example: - ``ghc -c Foo.hs`` +**No ``-O*``-type option specified:** This is taken to mean “Please +compile quickly; I'm not over-bothered about compiled-code quality.” +So, for example, ``ghc -c Foo.hs`` .. ghc-flag:: -O0 From git at git.haskell.org Wed Jun 14 20:52:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jun 2017 20:52:45 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Remove references to static flags in flag reference (bcb9185) Message-ID: <20170614205245.973773A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/bcb9185c75cd9f9ea40b1b32b08105241c3363d2/ghc >--------------------------------------------------------------- commit bcb9185c75cd9f9ea40b1b32b08105241c3363d2 Author: Ryan Scott Date: Fri Jun 2 11:48:57 2017 -0400 Remove references to static flags in flag reference A follow-up to #8440 (Ditch static flags). There are still some lingering references to static flags in the flag reference, so let's modify those references accordingly. Test Plan: Build the documentation Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3615 (cherry picked from commit bf775e9d6895c07f629409ee18503f40730cb5a0) >--------------------------------------------------------------- bcb9185c75cd9f9ea40b1b32b08105241c3363d2 utils/mkUserGuidePart/Main.hs | 3 +-- utils/mkUserGuidePart/Options/CompilerDebugging.hs | 4 ++-- utils/mkUserGuidePart/Options/Optimizations.hs | 4 ++-- utils/mkUserGuidePart/Types.hs | 4 +--- 4 files changed, 6 insertions(+), 9 deletions(-) diff --git a/utils/mkUserGuidePart/Main.hs b/utils/mkUserGuidePart/Main.hs index 344c808..d517048 100644 --- a/utils/mkUserGuidePart/Main.hs +++ b/utils/mkUserGuidePart/Main.hs @@ -49,7 +49,7 @@ whatGlasgowExtsDoes = unlines flagsTable :: [Flag] -> ReST flagsTable theFlags = table [50, 100, 30, 55] - ["Flag", "Description", "Static/Dynamic", "Reverse"] + ["Flag", "Description", "Type", "Reverse"] (map flagRow theFlags) where flagRow flag = @@ -60,7 +60,6 @@ flagsTable theFlags = ] where type_ = case flagType flag of - StaticFlag -> "static" DynamicFlag -> "dynamic" DynamicSettableFlag -> "dynamic/``:set``" ModeFlag -> "mode" diff --git a/utils/mkUserGuidePart/Options/CompilerDebugging.hs b/utils/mkUserGuidePart/Options/CompilerDebugging.hs index c886156..9704020 100644 --- a/utils/mkUserGuidePart/Options/CompilerDebugging.hs +++ b/utils/mkUserGuidePart/Options/CompilerDebugging.hs @@ -175,11 +175,11 @@ compilerDebuggingOptions = } , flag { flagName = "-dno-debug-output" , flagDescription = "Suppress unsolicited debugging output" - , flagType = StaticFlag + , flagType = DynamicFlag } , flag { flagName = "-dppr-debug" , flagDescription = "Turn on debug printing (more verbose)" - , flagType = StaticFlag + , flagType = DynamicFlag } , flag { flagName = "-dppr-user-length" , flagDescription = diff --git a/utils/mkUserGuidePart/Options/Optimizations.hs b/utils/mkUserGuidePart/Options/Optimizations.hs index b0f9bc5..f71a762 100644 --- a/utils/mkUserGuidePart/Options/Optimizations.hs +++ b/utils/mkUserGuidePart/Options/Optimizations.hs @@ -202,7 +202,7 @@ optimizationsOptions = } , flag { flagName = "-fno-opt-coercion" , flagDescription = "Turn off the coercion optimiser" - , flagType = StaticFlag + , flagType = DynamicFlag } , flag { flagName = "-fno-pre-inlining" , flagDescription = "Turn off pre-inlining" @@ -213,7 +213,7 @@ optimizationsOptions = "Turn off the \"state hack\" whereby any lambda with a real-world "++ "state token as argument is considered to be single-entry. Hence "++ "OK to inline things inside it." - , flagType = StaticFlag + , flagType = DynamicFlag } , flag { flagName = "-fomit-interface-pragmas" , flagDescription = diff --git a/utils/mkUserGuidePart/Types.hs b/utils/mkUserGuidePart/Types.hs index 33474da..340672e 100644 --- a/utils/mkUserGuidePart/Types.hs +++ b/utils/mkUserGuidePart/Types.hs @@ -1,8 +1,6 @@ module Types where -data FlagType = StaticFlag - -- ^ Static flag - | DynamicFlag +data FlagType = DynamicFlag -- ^ Dynamic flag | DynamicSettableFlag -- ^ Dynamic flag on which @:set@ can be used in GHCi From git at git.haskell.org Wed Jun 14 22:13:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jun 2017 22:13:08 +0000 (UTC) Subject: [commit: ghc] branch 'wip/D3646' created Message-ID: <20170614221308.5DFCB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/D3646 Referencing: 9f86f367b4eba8cb594a6fcc572ffbd7ac30467d From git at git.haskell.org Wed Jun 14 22:13:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jun 2017 22:13:11 +0000 (UTC) Subject: [commit: ghc] wip/D3646: Make module membership on ModuleGraph faster (9f86f36) Message-ID: <20170614221311.2DF3B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/D3646 Link : http://ghc.haskell.org/trac/ghc/changeset/9f86f367b4eba8cb594a6fcc572ffbd7ac30467d/ghc >--------------------------------------------------------------- commit 9f86f367b4eba8cb594a6fcc572ffbd7ac30467d Author: Bartosz Nitka Date: Wed May 31 10:47:03 2017 -0700 Make module membership on ModuleGraph faster Summary: 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: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3646 >--------------------------------------------------------------- 9f86f367b4eba8cb594a6fcc572ffbd7ac30467d compiler/backpack/DriverBkp.hs | 5 +- compiler/main/DriverMkDepend.hs | 16 ++-- compiler/main/DriverPipeline.hs | 5 +- compiler/main/GHC.hs | 23 ++--- compiler/main/GhcMake.hs | 54 ++++++----- compiler/main/HscMain.hs | 2 +- compiler/main/HscTypes.hs | 123 ++++++++++++++++++++++++-- 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 +- 13 files changed, 200 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 9f86f367b4eba8cb594a6fcc572ffbd7ac30467d From git at git.haskell.org Thu Jun 15 03:03:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Jun 2017 03:03:44 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: testsuite: Bump T9675 allocations (b0b330e) Message-ID: <20170615030344.45C1C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/b0b330e97255577d4aade1152ef2db30114a6688/ghc >--------------------------------------------------------------- commit b0b330e97255577d4aade1152ef2db30114a6688 Author: Ben Gamari Date: Wed Jun 14 21:33:21 2017 -0400 testsuite: Bump T9675 allocations >--------------------------------------------------------------- b0b330e97255577d4aade1152ef2db30114a6688 testsuite/tests/perf/compiler/all.T | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index c1a4bba..281615a 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -740,7 +740,7 @@ test('T9020', test('T9675', [ only_ways(['optasm']), compiler_stats_num_field('max_bytes_used', # Note [residency] - [(wordsize(64), 17675240, 15), + [(wordsize(64), 25234080, 15), # 2014-10-13 29596552 # 2014-10-13 26570896 seq the DmdEnv in seqDmdType as well # 2014-10-13 18582472 different machines giving different results.. @@ -750,13 +750,14 @@ test('T9675', # 2015-12-11 30837312 TypeInType (see #11196) # 2016-03-14 38776008 Final demand analyzer run # 2016-04-01 29871032 Fix leaks in demand analysis - # 2016-04-30 17675240 Fix leaks in tidy unfoldings + # 2017-04-30 17675240 Fix leaks in tidy unfoldings + # 2017-06-14 25234080 Unknown (wordsize(32), 18043224, 15) # 2015-07-11 15341228 (x86/Linux, 64-bit machine) use +RTS -G1 # 2016-04-06 18043224 (x86/Linux, 64-bit machine) ]), compiler_stats_num_field('peak_megabytes_allocated', # Note [residency] - [(wordsize(64), 63, 15), + [(wordsize(64), 93, 15), # 2014-10-13 66 # 2014-10-13 58 seq the DmdEnv in seqDmdType as well # 2014-10-13 49 different machines giving different results... @@ -768,6 +769,7 @@ test('T9675', # 2016-04-14 144 Final demand analyzer run # 2016-07-26 121 Unboxed sums? # 2017-04-30 63 Fix leaks in tidy unfoldings + # 2017-06-14 93 Unknown (wordsize(32), 56, 15) # 2015-07-11 56 (x86/Linux, 64-bit machine) use +RTS -G1 ]), From git at git.haskell.org Thu Jun 15 03:03:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Jun 2017 03:03:48 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Stop the specialiser generating loopy code (a7a1d7f) Message-ID: <20170615030348.AE8243A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/a7a1d7fdcd3e34787f28be4eb24645c2e14a9f3d/ghc >--------------------------------------------------------------- commit a7a1d7fdcd3e34787f28be4eb24645c2e14a9f3d Author: Simon Peyton Jones Date: Wed Jun 7 12:03:51 2017 +0100 Stop the specialiser generating loopy code This patch fixes a bad bug in the specialiser, which showed up as Trac #13429. When specialising an imported DFun, the specialiser could generate a recusive loop where none existed in the original program. It's all rather tricky, and I've documented it at some length in Note [Avoiding loops] We'd encoutered exactly this before (Trac #3591) but I had failed to realise that the very same thing could happen for /imported/ DFuns. I did quite a bit of refactoring. The compiler seems to get a tiny bit faster on deriving/perf/T10858 but almost all the gain had occurred before now; this patch just pushed it over the line. (cherry picked from commit 2b74bd9d8b4c6b20f3e8d9ada12e7db645cc3c19) >--------------------------------------------------------------- a7a1d7fdcd3e34787f28be4eb24645c2e14a9f3d compiler/specialise/Specialise.hs | 413 ++++++++++++--------- testsuite/tests/deriving/perf/all.T | 4 +- testsuite/tests/simplCore/should_compile/T13429.hs | 114 ------ testsuite/tests/simplCore/should_compile/all.T | 1 - testsuite/tests/simplCore/should_run/T13429.hs | 63 ++++ .../tests/simplCore/should_run/T13429.stdout | 0 testsuite/tests/simplCore/should_run/T13429_2.hs | 10 + .../tests/simplCore/should_run/T13429_2.stdout | 1 + testsuite/tests/simplCore/should_run/T13429_2a.hs | 37 ++ testsuite/tests/simplCore/should_run/T13429a.hs | 343 +++++++++++++++++ testsuite/tests/simplCore/should_run/all.T | 2 + 11 files changed, 699 insertions(+), 289 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 a7a1d7fdcd3e34787f28be4eb24645c2e14a9f3d From git at git.haskell.org Thu Jun 15 03:03:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Jun 2017 03:03:51 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Make CallInfo into a data type with fields (24f9d07) Message-ID: <20170615030351.627373A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/24f9d0754b318ca01be3ce89acd9f6d3165ce239/ghc >--------------------------------------------------------------- commit 24f9d0754b318ca01be3ce89acd9f6d3165ce239 Author: Simon Peyton Jones Date: Mon May 8 16:50:37 2017 +0100 Make CallInfo into a data type with fields Simple refactor, no change in behaviour (cherry picked from commit cb5ca5f39c2ad26608516ee4248b9ddea31a1d5a) >--------------------------------------------------------------- 24f9d0754b318ca01be3ce89acd9f6d3165ce239 compiler/specialise/Specialise.hs | 57 ++++++++++++++++++++++++--------------- 1 file changed, 36 insertions(+), 21 deletions(-) diff --git a/compiler/specialise/Specialise.hs b/compiler/specialise/Specialise.hs index 0dd295d..6eeea06 100644 --- a/compiler/specialise/Specialise.hs +++ b/compiler/specialise/Specialise.hs @@ -1224,7 +1224,7 @@ specCalls mb_mod env rules_for_me calls_for_me fn rhs -> SpecM (Maybe ((Id,CoreExpr), -- Specialised definition UsageDetails, -- Usage details from specialised body CoreRule)) -- Info for the Id's SpecEnv - spec_call _call_info@(CallKey call_ts, (call_ds, _)) + spec_call (CI { ci_key = CallKey call_ts, ci_args = call_ds }) = ASSERT( call_ts `lengthIs` n_tyvars && call_ds `lengthIs` n_dicts ) -- Suppose f's defn is f = /\ a b c -> \ d1 d2 -> rhs @@ -1768,8 +1768,6 @@ instance Outputable UsageDetails where -- variables (both type variables and dictionaries) type DictBind = (CoreBind, VarSet) -type DictExpr = CoreExpr - emptyUDs :: UsageDetails emptyUDs = MkUD { ud_binds = emptyBag, ud_calls = emptyDVarEnv } @@ -1778,13 +1776,25 @@ type CallDetails = DIdEnv CallInfoSet -- The order of specialized binds and rules depends on how we linearize -- CallDetails, so to get determinism we must use a deterministic set here. -- See Note [Deterministic UniqFM] in UniqDFM -newtype CallKey = CallKey [Maybe Type] - -- Nothing => unconstrained type argument data CallInfoSet = CIS Id (Bag CallInfo) -- The list of types and dictionaries is guaranteed to -- match the type of f +data CallInfo + = CI { ci_key :: CallKey -- Type arguments + , ci_args :: [DictExpr] -- Dictionary arguments + , ci_fvs :: VarSet -- Free vars of the ci_key and ci_args + -- call (including tyvars) + -- [*not* include the main id itself, of course] + } + +newtype CallKey = CallKey [Maybe Type] + -- Nothing => unconstrained type argument + +type DictExpr = CoreExpr + + {- Note [CallInfoSet determinism] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1829,7 +1839,7 @@ ciSetToList (CIS _ b) = snd $ foldrBag combine (emptyTM, []) b -- This is where we eliminate duplicates, recording the CallKeys we've -- already seen in the TrieMap. See Note [CallInfoSet determinism]. combine :: CallInfo -> (CallKeySet, [CallInfo]) -> (CallKeySet, [CallInfo]) - combine ci@(CallKey key, _) (set, acc) + combine ci@(CI { ci_key = CallKey key }) (set, acc) | Just _ <- lookupTM key set = (set, acc) | otherwise = (insertTM key () set, ci:acc) @@ -1839,26 +1849,24 @@ type CallKeySet = ListMap (MaybeMap TypeMap) () ciSetFilter :: (CallInfo -> Bool) -> CallInfoSet -> CallInfoSet ciSetFilter p (CIS id a) = CIS id (filterBag p a) -type CallInfo = (CallKey, ([DictExpr], VarSet)) - -- Range is dict args and the vars of the whole - -- call (including tyvars) - -- [*not* include the main id itself, of course] - instance Outputable CallInfoSet where ppr (CIS fn map) = hang (text "CIS" <+> ppr fn) 2 (ppr map) pprCallInfo :: Id -> CallInfo -> SDoc -pprCallInfo fn (CallKey mb_tys, (_dxs, _)) - = hang (ppr fn) - 2 (fsep (map ppr_call_key_ty mb_tys {- ++ map pprParendExpr _dxs -})) +pprCallInfo fn (CI { ci_key = key }) + = ppr fn <+> ppr key ppr_call_key_ty :: Maybe Type -> SDoc ppr_call_key_ty Nothing = char '_' ppr_call_key_ty (Just ty) = char '@' <+> pprParendType ty instance Outputable CallKey where - ppr (CallKey ts) = ppr ts + ppr (CallKey ts) = brackets (fsep (map ppr_call_key_ty ts)) + +instance Outputable CallInfo where + ppr (CI { ci_key = key, ci_args = args, ci_fvs = fvs }) + = text "CI" <> braces (hsep [ ppr key, ppr args, ppr fvs ]) unionCalls :: CallDetails -> CallDetails -> CallDetails unionCalls c1 c2 = plusDVarEnv_C unionCallInfoSet c1 c2 @@ -1875,14 +1883,16 @@ callDetailsFVs calls = callInfoFVs :: CallInfoSet -> VarSet callInfoFVs (CIS _ call_info) = - foldrBag (\(_, (_,fv)) vs -> unionVarSet fv vs) emptyVarSet call_info + foldrBag (\(CI { ci_fvs = fv }) vs -> unionVarSet fv vs) emptyVarSet call_info ------------------------------------------------------------ singleCall :: Id -> [Maybe Type] -> [DictExpr] -> UsageDetails singleCall id tys dicts = MkUD {ud_binds = emptyBag, ud_calls = unitDVarEnv id $ CIS id $ - unitBag (CallKey tys, (dicts, call_fvs)) } + unitBag (CI { ci_key = CallKey tys + , ci_args = dicts + , ci_fvs = call_fvs }) } where call_fvs = exprsFreeVars dicts `unionVarSet` tys_fvs tys_fvs = tyCoVarsOfTypes (catMaybes tys) @@ -2146,11 +2156,16 @@ callsForMe fn (MkUD { ud_binds = orig_dbs, ud_calls = orig_calls }) filter_dfuns | isDFunId fn = filter ok_call | otherwise = \cs -> cs - ok_call (_, (_,fvs)) = not (fvs `intersectsVarSet` dep_set) + ok_call (CI { ci_fvs = fvs }) = not (fvs `intersectsVarSet` dep_set) ---------------------- splitDictBinds :: Bag DictBind -> IdSet -> (Bag DictBind, Bag DictBind, IdSet) --- Returns (free_dbs, dump_dbs, dump_set) +-- splitDictBinds dbs bndrs returns +-- (free_dbs, dump_dbs, dump_set) +-- where +-- * dump_dbs depends, transitively on bndrs +-- * free_dbs does not depend on bndrs +-- * dump_set = bndrs `union` bndrs(dump_dbs) splitDictBinds dbs bndr_set = foldlBag split_db (emptyBag, emptyBag, bndr_set) dbs -- Important that it's foldl not foldr; @@ -2167,11 +2182,11 @@ splitDictBinds dbs bndr_set ---------------------- deleteCallsMentioning :: VarSet -> CallDetails -> CallDetails --- Remove calls *mentioning* bs +-- Remove calls *mentioning* bs in any way deleteCallsMentioning bs calls = mapDVarEnv (ciSetFilter keep_call) calls where - keep_call (_, (_, fvs)) = not (fvs `intersectsVarSet` bs) + keep_call (CI { ci_fvs = fvs }) = not (fvs `intersectsVarSet` bs) deleteCallsFor :: [Id] -> CallDetails -> CallDetails -- Remove calls *for* bs From git at git.haskell.org Fri Jun 16 19:19:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jun 2017 19:19:10 +0000 (UTC) Subject: [commit: ghc] master: base: Validate input in setNumCapabilities (9849403) Message-ID: <20170616191910.C001A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9849403147b584ff160daeb4f13bf36adb2bab2e/ghc >--------------------------------------------------------------- commit 9849403147b584ff160daeb4f13bf36adb2bab2e Author: Ben Gamari Date: Fri Jun 16 15:18:48 2017 -0400 base: Validate input in setNumCapabilities Test Plan: validate Reviewers: austin, hvr, erikd, simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13832 Differential Revision: https://phabricator.haskell.org/D3652 >--------------------------------------------------------------- 9849403147b584ff160daeb4f13bf36adb2bab2e libraries/base/GHC/Conc/Sync.hs | 4 +++- testsuite/tests/rts/T13832.hs | 4 ++++ testsuite/tests/rts/T13832.stderr | 1 + testsuite/tests/rts/all.T | 2 +- 4 files changed, 9 insertions(+), 2 deletions(-) diff --git a/libraries/base/GHC/Conc/Sync.hs b/libraries/base/GHC/Conc/Sync.hs index 78a0334..44d34d8 100644 --- a/libraries/base/GHC/Conc/Sync.hs +++ b/libraries/base/GHC/Conc/Sync.hs @@ -379,7 +379,9 @@ to avoid contention with other processes in the machine. @since 4.5.0.0 -} setNumCapabilities :: Int -> IO () -setNumCapabilities i = c_setNumCapabilities (fromIntegral i) +setNumCapabilities i + | i <= 0 = fail $ "setNumCapabilities: Capability count ("++show i++") must be positive" + | otherwise = c_setNumCapabilities (fromIntegral i) foreign import ccall safe "setNumCapabilities" c_setNumCapabilities :: CUInt -> IO () diff --git a/testsuite/tests/rts/T13832.hs b/testsuite/tests/rts/T13832.hs new file mode 100644 index 0000000..47d9ed2 --- /dev/null +++ b/testsuite/tests/rts/T13832.hs @@ -0,0 +1,4 @@ +import GHC.Conc + +main :: IO () +main = setNumCapabilities 0 diff --git a/testsuite/tests/rts/T13832.stderr b/testsuite/tests/rts/T13832.stderr new file mode 100644 index 0000000..7a552ca --- /dev/null +++ b/testsuite/tests/rts/T13832.stderr @@ -0,0 +1 @@ +T13832: user error (setNumCapabilities: Capability count (0) must be positive) diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index fc7363f..f32a35b 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -372,4 +372,4 @@ test('T12497', [ unless(opsys('mingw32'), skip) run_command, ['$MAKE -s --no-print-directory T12497']) test('T12903', [when(opsys('mingw32'), skip)], compile_and_run, ['']) - +test('T13832', exit_code(1), compile_and_run, ['-threaded']) From git at git.haskell.org Fri Jun 16 21:00:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jun 2017 21:00:27 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump time submodule to 1.8.0.2 (a5e045a) Message-ID: <20170616210027.05E4A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/a5e045af9b51da43b7e743134fafedf56ae4f7e5/ghc >--------------------------------------------------------------- commit a5e045af9b51da43b7e743134fafedf56ae4f7e5 Author: Ben Gamari Date: Mon Jun 12 15:04:21 2017 -0400 Bump time submodule to 1.8.0.2 >--------------------------------------------------------------- a5e045af9b51da43b7e743134fafedf56ae4f7e5 libraries/time | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) 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 From git at git.haskell.org Fri Jun 16 21:00:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jun 2017 21:00:35 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: build.mk: Disable -g by default (1767f54) Message-ID: <20170616210035.2FB8A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/1767f542a73b05c8821d61a60cdc0aae102a8cd4/ghc >--------------------------------------------------------------- commit 1767f542a73b05c8821d61a60cdc0aae102a8cd4 Author: Ben Gamari Date: Sun Jun 11 10:13:44 2017 -0400 build.mk: Disable -g by default >--------------------------------------------------------------- 1767f542a73b05c8821d61a60cdc0aae102a8cd4 mk/build.mk.sample | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/mk/build.mk.sample b/mk/build.mk.sample index 685d83c..6bceca3 100644 --- a/mk/build.mk.sample +++ b/mk/build.mk.sample @@ -83,8 +83,8 @@ endif # This is necessary, for instance, to get DWARF stack traces out of programs # built by the produced compiler. You must also pass --enable-dwarf-unwind to # `configure` to enable the runtime system's builtin unwinding support. -GhcLibHcOpts += -g3 -GhcRtsHcOpts += -g3 +#GhcLibHcOpts += -g3 +#GhcRtsHcOpts += -g3 # Build the "extra" packages (see ./packages). This enables more tests. See: # https://ghc.haskell.org/trac/ghc/wiki/Building/RunningTests/Running#AdditionalPackages From git at git.haskell.org Fri Jun 16 21:00:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jun 2017 21:00:29 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix a lost-wakeup bug in BLACKHOLE handling (#13751) (62a4f06) Message-ID: <20170616210029.C2FEB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/62a4f066e8783f9c5f2bbaad37464e79711accfa/ghc >--------------------------------------------------------------- commit 62a4f066e8783f9c5f2bbaad37464e79711accfa Author: Simon Marlow Date: Sat Jun 3 20:26:13 2017 +0100 Fix a lost-wakeup bug in BLACKHOLE handling (#13751) Summary: The problem occurred when * Threads A & B evaluate the same thunk * Thread A context-switches, so the thunk gets blackholed * Thread C enters the blackhole, creates a BLOCKING_QUEUE attached to the blackhole and thread A's `tso->bq` queue * Thread B updates the blackhole with a value, overwriting the BLOCKING_QUEUE * We GC, replacing A's update frame with stg_enter_checkbh * Throw an exception in A, which ignores the stg_enter_checkbh frame Now we have C blocked on A's tso->bq queue, but we forgot to check the queue because the stg_enter_checkbh frame has been thrown away by the exception. The solution and alternative designs are discussed in Note [upd-black-hole]. This also exposed a bug in the interpreter, whereby we were sometimes context-switching without calling `threadPaused()`. I've fixed this and added some Notes. Test Plan: * `cd testsuite/tests/concurrent && make slow` * validate Reviewers: niteria, bgamari, austin, erikd Reviewed By: erikd Subscribers: rwbarton, thomie GHC Trac Issues: #13751 Differential Revision: https://phabricator.haskell.org/D3630 (cherry picked from commit 598472908ebb08f6811b892f285490554c290ae3) >--------------------------------------------------------------- 62a4f066e8783f9c5f2bbaad37464e79711accfa includes/stg/MiscClosures.h | 2 - rts/HeapStackCheck.cmm | 24 ---------- rts/Interpreter.c | 10 +++++ rts/Messages.c | 4 +- rts/Schedule.c | 7 ++- rts/StgStartup.cmm | 3 ++ rts/sm/Evac.c | 64 +++++++++++++++++++++++++- rts/sm/Evac.h | 3 ++ rts/sm/Scav.c | 70 +++++++++++++++++++---------- testsuite/tests/concurrent/should_run/all.T | 1 + 10 files changed, 133 insertions(+), 55 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 62a4f066e8783f9c5f2bbaad37464e79711accfa From git at git.haskell.org Fri Jun 16 21:00:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jun 2017 21:00:32 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump haddock submodule (5eb0545) Message-ID: <20170616210032.76B0C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/5eb05459c9521c8893d471a0346056343be2cf6e/ghc >--------------------------------------------------------------- commit 5eb05459c9521c8893d471a0346056343be2cf6e Author: Ben Gamari Date: Fri Jun 9 14:39:18 2017 -0400 Bump haddock submodule >--------------------------------------------------------------- 5eb05459c9521c8893d471a0346056343be2cf6e testsuite/tests/perf/haddock/all.T | 6 ++++-- utils/haddock | 2 +- 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index 7e53386..ef3ad38 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), 25592972912, 5) + ,(wordsize(64), 19573969096, 5) # 2012-08-14: 5920822352 (amd64/Linux) # 2012-09-20: 5829972376 (amd64/Linux) # 2012-10-08: 5902601224 (amd64/Linux) @@ -39,6 +39,7 @@ test('haddock.base', # 2017-02-16: 32695562088 Better Lint for join points # 2017-02-17: 38425793776 (x86_64/Linux) - Generalize kind of (->) # 2017-02-12: 25592972912 (x86_64/Linux) - Type-indexed Typeable + # 2017-06-16: 19573969096 (x86_64/Linux) - Don't desugar for haddock ,(platform('i386-unknown-mingw32'), 2885173512, 5) # 2013-02-10: 3358693084 (x86/Windows) @@ -64,7 +65,7 @@ test('haddock.Cabal', [extra_files(['../../../../libraries/Cabal/Cabal/dist-install/haddock.t']), unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 18865432648, 5) + [(wordsize(64), 15717181064, 5) # 2012-08-14: 3255435248 (amd64/Linux) # 2012-08-29: 3324606664 (amd64/Linux, new codegen) # 2012-10-08: 3373401360 (amd64/Linux) @@ -109,6 +110,7 @@ test('haddock.Cabal', # 2017-02-16: 23867276992 Better Lint for join points # 2017-02-17: 27784875792 (amd64/Linux) - Generalize kind of (->) # 2017-02-12: 18865432648 (amd64/Linux) - Type-indexed Typeable + # 2017-06-16: 15717181064 (amd64/Linux) - Don't desugar for haddock ,(platform('i386-unknown-mingw32'), 3293415576, 5) # 2012-10-30: 1733638168 (x86/Windows) diff --git a/utils/haddock b/utils/haddock index e0e6615..87c551f 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit e0e6615dd421f1b332ce2b11a98de768fa7c29a8 +Subproject commit 87c551fc668b9251f2647cce8772f205e1cee154 From git at git.haskell.org Fri Jun 16 21:00:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jun 2017 21:00:38 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix #13807 - foreign import nondeterminism (40f4efb) Message-ID: <20170616210038.C403D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/40f4efb18c12d42d7ac735224e105bd177fe0e16/ghc >--------------------------------------------------------------- commit 40f4efb18c12d42d7ac735224e105bd177fe0e16 Author: Bartosz Nitka Date: Mon Jun 12 17:02:44 2017 -0400 Fix #13807 - foreign import nondeterminism The problem was that the generated label included a freshly assigned Unique value. Test Plan: Added a new test and looked at the generated stub: ``` #include "HsFFI.h" #ifdef __cplusplus extern "C" { #endif extern HsInt zdmainzdAzdAzuzzlzzgzzg(StgStablePtr the_stableptr); extern HsInt zdmainzdAzdAzumkStringWriter(StgStablePtr the_stableptr); #ifdef __cplusplus } #endif ``` ./validate Reviewers: simonmar, austin, bgamari Reviewed By: simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13807 Differential Revision: https://phabricator.haskell.org/D3633 (cherry picked from commit dcdc391609d6ff902989d806266855901c051608) >--------------------------------------------------------------- 40f4efb18c12d42d7ac735224e105bd177fe0e16 compiler/deSugar/DsForeign.hs | 13 +++++-------- testsuite/tests/determinism/T13807/A.hs | 11 +++++++++++ testsuite/tests/determinism/{determ022 => T13807}/Makefile | 2 +- .../{determ002/determ002.stdout => T13807/T13807.stdout} | 0 testsuite/tests/determinism/T13807/all.T | 1 + 5 files changed, 18 insertions(+), 9 deletions(-) diff --git a/compiler/deSugar/DsForeign.hs b/compiler/deSugar/DsForeign.hs index 9998a4d..65dc16a 100644 --- a/compiler/deSugar/DsForeign.hs +++ b/compiler/deSugar/DsForeign.hs @@ -50,6 +50,7 @@ import OrdList import Pair import Util import Hooks +import Encoding import Data.Maybe import Data.List @@ -410,16 +411,12 @@ dsFExportDynamic :: Id -> CCallConv -> DsM ([Binding], SDoc, SDoc) dsFExportDynamic id co0 cconv = do - fe_id <- newSysLocalDs ty mod <- getModule dflags <- getDynFlags - let - -- hack: need to get at the name of the C stub we're about to generate. - -- TODO: There's no real need to go via String with - -- (mkFastString . zString). In fact, is there a reason to convert - -- to FastString at all now, rather than sticking with FastZString? - fe_nm = mkFastString (zString (zEncodeFS (moduleNameFS (moduleName mod))) ++ "_" ++ toCName dflags fe_id) - + let fe_nm = mkFastString $ zEncodeString + (moduleStableString mod ++ "$" ++ toCName dflags id) + -- Construct the label based on the passed id, don't use names + -- depending on Unique. See #13807 and Note [Unique Determinism]. cback <- newSysLocalDs arg_ty newStablePtrId <- dsLookupGlobalId newStablePtrName stable_ptr_tycon <- dsLookupTyCon stablePtrTyConName diff --git a/testsuite/tests/determinism/T13807/A.hs b/testsuite/tests/determinism/T13807/A.hs new file mode 100644 index 0000000..ff8a00c --- /dev/null +++ b/testsuite/tests/determinism/T13807/A.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE ForeignFunctionInterface #-} + +module A ( mkStringWriter, (<>>) ) where + +import Foreign.Ptr +import Prelude + +-- generated C wrappers used to use Unique values for the label +foreign import ccall "wrapper" mkStringWriter :: Int -> IO (Ptr Int) +-- make sure we properly z-encode the generated stubs +foreign import ccall "wrapper" (<>>) :: Int -> IO (Ptr Int) diff --git a/testsuite/tests/determinism/determ022/Makefile b/testsuite/tests/determinism/T13807/Makefile similarity index 96% copy from testsuite/tests/determinism/determ022/Makefile copy to testsuite/tests/determinism/T13807/Makefile index 1bd543e..f420abb 100644 --- a/testsuite/tests/determinism/determ022/Makefile +++ b/testsuite/tests/determinism/T13807/Makefile @@ -2,7 +2,7 @@ TOP=../../.. include $(TOP)/mk/boilerplate.mk include $(TOP)/mk/test.mk -determ022: +T13807: $(RM) A.hi A.o '$(TEST_HC)' $(TEST_HC_OPTS) -O -dinitial-unique=0 -dunique-increment=1 A.hs $(CP) A.hi A.normal.hi diff --git a/testsuite/tests/determinism/determ002/determ002.stdout b/testsuite/tests/determinism/T13807/T13807.stdout similarity index 100% copy from testsuite/tests/determinism/determ002/determ002.stdout copy to testsuite/tests/determinism/T13807/T13807.stdout diff --git a/testsuite/tests/determinism/T13807/all.T b/testsuite/tests/determinism/T13807/all.T new file mode 100644 index 0000000..465d57c --- /dev/null +++ b/testsuite/tests/determinism/T13807/all.T @@ -0,0 +1 @@ +test('T13807', [extra_files(['A.hs'])], run_command, ['$MAKE -s --no-print-directory T13807']) From git at git.haskell.org Fri Jun 16 21:00:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jun 2017 21:00:41 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: users-guide: Document multi-line DEPRECATED pragmas (d8794aa) Message-ID: <20170616210041.8ED573A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/d8794aa582687846178a0b11604b736212cbf936/ghc >--------------------------------------------------------------- commit d8794aa582687846178a0b11604b736212cbf936 Author: Ben Gamari Date: Mon Jun 12 17:00:55 2017 -0400 users-guide: Document multi-line DEPRECATED pragmas Fixes #13791. [skip ci] Test Plan: Read it Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #13791 Differential Revision: https://phabricator.haskell.org/D3639 (cherry picked from commit 8f72608953fee7ff77a6d89b00f25749261b8820) >--------------------------------------------------------------- d8794aa582687846178a0b11604b736212cbf936 docs/users_guide/glasgow_exts.rst | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 4a7ef74..5b71c02 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -12503,6 +12503,12 @@ are two ways of using these pragmas. both are in scope. If both are in scope, there is currently no way to specify one without the other (c.f. fixities :ref:`infix-tycons`). +Also note that the argument to ``DEPRECATED`` and ``WARNING`` can also be a list +of strings, in which case the strings will be presented on separate lines in the +resulting warning message, :: + + {-# DEPRECATED foo, bar ["Don't use these", "Use gar instead"] #-} + Warnings and deprecations are not reported for (a) uses within the defining module, (b) defining a method in a class instance, and (c) uses in an export list. The latter reduces spurious complaints within a From git at git.haskell.org Fri Jun 16 21:00:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jun 2017 21:00:44 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: base: Validate input in setNumCapabilities (a4e7820) Message-ID: <20170616210044.A9EEE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/a4e782087ae0df211f8d48c11ded0b1dd81f40a4/ghc >--------------------------------------------------------------- commit a4e782087ae0df211f8d48c11ded0b1dd81f40a4 Author: Ben Gamari Date: Fri Jun 16 15:18:48 2017 -0400 base: Validate input in setNumCapabilities Test Plan: validate Reviewers: austin, hvr, erikd, simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13832 Differential Revision: https://phabricator.haskell.org/D3652 (cherry picked from commit 9849403147b584ff160daeb4f13bf36adb2bab2e) >--------------------------------------------------------------- a4e782087ae0df211f8d48c11ded0b1dd81f40a4 libraries/base/GHC/Conc/Sync.hs | 4 +++- testsuite/tests/rts/T13832.hs | 4 ++++ testsuite/tests/rts/T13832.stderr | 1 + testsuite/tests/rts/all.T | 2 +- 4 files changed, 9 insertions(+), 2 deletions(-) diff --git a/libraries/base/GHC/Conc/Sync.hs b/libraries/base/GHC/Conc/Sync.hs index 78a0334..44d34d8 100644 --- a/libraries/base/GHC/Conc/Sync.hs +++ b/libraries/base/GHC/Conc/Sync.hs @@ -379,7 +379,9 @@ to avoid contention with other processes in the machine. @since 4.5.0.0 -} setNumCapabilities :: Int -> IO () -setNumCapabilities i = c_setNumCapabilities (fromIntegral i) +setNumCapabilities i + | i <= 0 = fail $ "setNumCapabilities: Capability count ("++show i++") must be positive" + | otherwise = c_setNumCapabilities (fromIntegral i) foreign import ccall safe "setNumCapabilities" c_setNumCapabilities :: CUInt -> IO () diff --git a/testsuite/tests/rts/T13832.hs b/testsuite/tests/rts/T13832.hs new file mode 100644 index 0000000..47d9ed2 --- /dev/null +++ b/testsuite/tests/rts/T13832.hs @@ -0,0 +1,4 @@ +import GHC.Conc + +main :: IO () +main = setNumCapabilities 0 diff --git a/testsuite/tests/rts/T13832.stderr b/testsuite/tests/rts/T13832.stderr new file mode 100644 index 0000000..7a552ca --- /dev/null +++ b/testsuite/tests/rts/T13832.stderr @@ -0,0 +1 @@ +T13832: user error (setNumCapabilities: Capability count (0) must be positive) diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index fc7363f..f32a35b 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -372,4 +372,4 @@ test('T12497', [ unless(opsys('mingw32'), skip) run_command, ['$MAKE -s --no-print-directory T12497']) test('T12903', [when(opsys('mingw32'), skip)], compile_and_run, ['']) - +test('T13832', exit_code(1), compile_and_run, ['-threaded']) From git at git.haskell.org Fri Jun 16 21:20:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jun 2017 21:20:44 +0000 (UTC) Subject: [commit: ghc] master: Fix the treatment of 'closed' definitions (dc8e686) Message-ID: <20170616212044.9726A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dc8e6861dc5586a8222484afc3bd26c432e2d69c/ghc >--------------------------------------------------------------- commit dc8e6861dc5586a8222484afc3bd26c432e2d69c Author: Simon Peyton Jones Date: Fri Jun 16 22:16:14 2017 +0100 Fix the treatment of 'closed' definitions The IdBindingInfo field of ATcId serves two purposes - to control generalisation when we have -XMonoLocalBinds - to check for floatability when dealing with (static e) These are related, but not the same, and they'd becomme confused. Trac #13804 showed this up via an example like this: f periph = let sr :: forall a. [a] -> [a] sr = if periph then reverse else id sr2 = sr -- The question: is sr2 generalised? -- It should be, because sr has a type sig -- even though it has periph free in (sr2 [True], sr2 "c") Here sr2 should be generalised, despite the free var 'periph' in 'sr' because 'sr' has a closed type signature. I documented all this very carefully this time, in TcRnTypes: Note [Meaning of IdBindingInfo] Note [Bindings with closed types: ClosedTypeId] >--------------------------------------------------------------- dc8e6861dc5586a8222484afc3bd26c432e2d69c compiler/main/StaticPtrTable.hs | 12 +- compiler/typecheck/TcBinds.hs | 87 ++++---- compiler/typecheck/TcEnv.hs | 88 ++++---- compiler/typecheck/TcRnTypes.hs | 231 +++++++++++++-------- compiler/typecheck/TcSigs.hs | 9 +- testsuite/tests/typecheck/should_compile/T13804.hs | 13 ++ testsuite/tests/typecheck/should_compile/all.T | 1 + 7 files changed, 263 insertions(+), 178 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 dc8e6861dc5586a8222484afc3bd26c432e2d69c From git at git.haskell.org Fri Jun 16 22:41:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jun 2017 22:41:13 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix the treatment of 'closed' definitions (15af715) Message-ID: <20170616224113.370343A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/15af7156087dec6b1031406bcbe4508b71cc3470/ghc >--------------------------------------------------------------- commit 15af7156087dec6b1031406bcbe4508b71cc3470 Author: Simon Peyton Jones Date: Fri Jun 16 22:16:14 2017 +0100 Fix the treatment of 'closed' definitions The IdBindingInfo field of ATcId serves two purposes - to control generalisation when we have -XMonoLocalBinds - to check for floatability when dealing with (static e) These are related, but not the same, and they'd becomme confused. Trac #13804 showed this up via an example like this: f periph = let sr :: forall a. [a] -> [a] sr = if periph then reverse else id sr2 = sr -- The question: is sr2 generalised? -- It should be, because sr has a type sig -- even though it has periph free in (sr2 [True], sr2 "c") Here sr2 should be generalised, despite the free var 'periph' in 'sr' because 'sr' has a closed type signature. I documented all this very carefully this time, in TcRnTypes: Note [Meaning of IdBindingInfo] Note [Bindings with closed types: ClosedTypeId] (cherry picked from commit dc8e6861dc5586a8222484afc3bd26c432e2d69c) >--------------------------------------------------------------- 15af7156087dec6b1031406bcbe4508b71cc3470 compiler/main/StaticPtrTable.hs | 12 +- compiler/typecheck/TcBinds.hs | 87 ++++---- compiler/typecheck/TcEnv.hs | 88 ++++---- compiler/typecheck/TcRnTypes.hs | 231 +++++++++++++-------- compiler/typecheck/TcSigs.hs | 9 +- testsuite/tests/typecheck/should_compile/T13804.hs | 13 ++ testsuite/tests/typecheck/should_compile/all.T | 1 + 7 files changed, 263 insertions(+), 178 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 15af7156087dec6b1031406bcbe4508b71cc3470 From git at git.haskell.org Fri Jun 16 22:41:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jun 2017 22:41:15 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: GHC.Stats cleanup (9670679) Message-ID: <20170616224115.DC9CC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/96706799d6cd3c077f31c93e468d6864c358dc09/ghc >--------------------------------------------------------------- commit 96706799d6cd3c077f31c93e468d6864c358dc09 Author: Ryan Scott Date: Fri Jun 2 11:52:41 2017 -0400 GHC.Stats cleanup This does two things: * The `RtsTime` type wasn't exported, but it is used as the type of several record fields. Let's export it and give it some documentation. * Neither `RTSStats` nor `GCDetails` have `Read` or `Show` instances, but `GCStats` does! Let's fix this discrepancy. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: goldfire, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3625 (cherry picked from commit 811a2986475d88f73bb22b4600970039e1b582d6) >--------------------------------------------------------------- 96706799d6cd3c077f31c93e468d6864c358dc09 libraries/base/GHC/Stats.hsc | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/libraries/base/GHC/Stats.hsc b/libraries/base/GHC/Stats.hsc index d5d48f5..c4e2e80 100644 --- a/libraries/base/GHC/Stats.hsc +++ b/libraries/base/GHC/Stats.hsc @@ -15,7 +15,7 @@ module GHC.Stats ( -- * Runtime statistics - RTSStats(..), GCDetails(..) + RTSStats(..), GCDetails(..), RtsTime , getRTSStats , getRTSStatsEnabled @@ -104,7 +104,7 @@ data RTSStats = RTSStats { -- | Details about the most recent GC , gc :: GCDetails - } + } deriving (Read, Show) -- -- | Statistics about a single GC. This is a mirror of the C @struct @@ -138,9 +138,9 @@ data GCDetails = GCDetails { , gcdetails_cpu_ns :: RtsTime -- | The time elapsed during GC itself , gcdetails_elapsed_ns :: RtsTime - } - + } deriving (Read, Show) +-- | Time values from the RTS, using a fixed resolution of nanoseconds. type RtsTime = Int64 -- @since 4.9.0.0 From git at git.haskell.org Fri Jun 16 23:49:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jun 2017 23:49:29 +0000 (UTC) Subject: [commit: ghc] master: Provide way to build using existing C compiler on Windows. (fda094d) Message-ID: <20170616234929.522A43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fda094d000cf2c2874a8205c8212cb83b52259ef/ghc >--------------------------------------------------------------- commit fda094d000cf2c2874a8205c8212cb83b52259ef Author: Tamar Christina Date: Sun Jun 11 11:40:11 2017 +0100 Provide way to build using existing C compiler on Windows. Summary: There are various distros that build GHC using their own C compilers such as MSYS2. Currently they have to patch the build scripts everytime. This patch provides the configure argument `--enable-distro-toolchain` which allows one to build using any C compiler on the path. This is also useful for testing new versions of GCC. Test Plan: ./configure --enable-distro-toolchain && make - && make THREADS=9 test ./validate Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, erikd, #ghc_windows_task_force GHC Trac Issues: #13792 Differential Revision: https://phabricator.haskell.org/D3637 >--------------------------------------------------------------- fda094d000cf2c2874a8205c8212cb83b52259ef aclocal.m4 | 22 ++++++++++++++----- configure.ac | 47 ++++++++++++++++++++++++++++++++++++---- docs/users_guide/8.4.1-notes.rst | 4 ++++ 3 files changed, 64 insertions(+), 9 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index d566f83..db394f3 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -460,7 +460,7 @@ AC_DEFUN([GET_ARM_ISA], # Set the variables used in the settings file AC_DEFUN([FP_SETTINGS], [ - if test "$windows" = YES + if test "$windows" = YES -a "$EnableDistroToolchain" = "NO" then mingw_bin_prefix=mingw/bin/ SettingsCCompilerCommand="\$topdir/../${mingw_bin_prefix}gcc.exe" @@ -472,6 +472,18 @@ AC_DEFUN([FP_SETTINGS], SettingsDllWrapCommand="\$topdir/../${mingw_bin_prefix}dllwrap.exe" SettingsWindresCommand="\$topdir/../${mingw_bin_prefix}windres.exe" SettingsTouchCommand='$topdir/bin/touchy.exe' + elif test "$EnableDistroToolchain" = "YES" + then + SettingsCCompilerCommand="$(basename $CC)" + SettingsCCompilerFlags="$CONF_CC_OPTS_STAGE2" + SettingsHaskellCPPCommand="$(basename $HaskellCPPCmd)" + SettingsHaskellCPPFlags="$HaskellCPPArgs" + SettingsLdCommand="$(basename $LdCmd)" + SettingsArCommand="$(basename $ArCmd)" + SettingsPerlCommand="$(basename $PerlCmd)" + SettingsDllWrapCommand="$(basename $DllWrapCmd)" + SettingsWindresCommand="$(basename $WindresCmd)" + SettingsTouchCommand='$topdir/bin/touchy.exe' else SettingsCCompilerCommand="$CC" SettingsHaskellCPPCommand="$HaskellCPPCmd" @@ -479,17 +491,17 @@ AC_DEFUN([FP_SETTINGS], SettingsLdCommand="$LdCmd" SettingsArCommand="$ArCmd" SettingsPerlCommand="$PerlCmd" - if test -z "$DllWrap" + if test -z "$DllWrapCmd" then SettingsDllWrapCommand="/bin/false" else - SettingsDllWrapCommand="$DllWrap" + SettingsDllWrapCommand="$DllWrapCmd" fi - if test -z "$Windres" + if test -z "$WindresCmd" then SettingsWindresCommand="/bin/false" else - SettingsWindresCommand="$Windres" + SettingsWindresCommand="$WindresCmd" fi SettingsTouchCommand='touch' fi diff --git a/configure.ac b/configure.ac index a32e6b4..721f0e7 100644 --- a/configure.ac +++ b/configure.ac @@ -113,6 +113,17 @@ AC_ARG_ENABLE(tarballs-autodownload, TarballsAutodownload=NO ) +AC_ARG_ENABLE(distro-toolchain, +[AC_HELP_STRING([--enable-distro-toolchain], + [Do not use bundled Windows toolchain binaries.])], + EnableDistroToolchain=YES, + EnableDistroToolchain=NO +) + +if test "$EnableDistroToolchain" = "YES"; then + TarballsAutodownload=NO +fi + dnl CC_STAGE0 is like the "previous" variable CC (inherited by CC_STAGE[123]) dnl but instead used by stage0 for bootstrapping stage1 AC_ARG_VAR(CC_STAGE0, [C compiler command (bootstrap)]) @@ -365,7 +376,7 @@ set_up_tarballs() { fi } -if test "$HostOS" = "mingw32" +if test "$HostOS" = "mingw32" -a "$EnableDistroToolchain" = "NO" then test -d inplace || mkdir inplace @@ -395,6 +406,29 @@ then fi fi +# We don't want to bundle a MinGW-w64 toolchain +# So we have to find these individual tools. +if test "$EnableDistroToolchain" = "YES" +then + # Ideally should use AC_CHECK_TARGET_TOOL but our triples + # are screwed up. Configure doesn't think they're ever equal and + # so never tried without the prefix. + AC_PATH_PROG([CC],[gcc], [clang]) + AC_PATH_PROG([LD],[ld], [lld]) + AC_PATH_PROG([NM],[nm]) + AC_PATH_PROG([AR],[ar]) + AC_PATH_PROG([RANLIB],[ranlib]) + AC_PATH_PROG([OBJDUMP],[objdump]) + AC_PATH_PROG([DllWrap],[dllwrap]) + AC_PATH_PROG([Windres],[windres]) + + DllWrapCmd="$DllWrap" + WindresCmd="$Windres" + + AC_SUBST([DllWrapCmd]) + AC_SUBST([WindresCmd]) +fi + FP_ICONV FP_GMP FP_CURSES @@ -461,6 +495,7 @@ fi AC_SUBST(CrossCompiling) AC_SUBST(CrossCompilePrefix) AC_SUBST(TargetPlatformFull) +AC_SUBST(EnableDistroToolchain) dnl ** Which gcc to use? dnl -------------------------------------------------------------- @@ -621,7 +656,11 @@ SplitObjsBroken=NO dnl ** look for `perl' case $HostOS_CPP in cygwin32|mingw32) - PerlCmd=$hardtop/inplace/perl/perl + if test "$EnableDistroToolchain" = "NO"; then + PerlCmd=$hardtop/inplace/perl/perl + else + AC_PATH_PROG([PerlCmd],[perl]) + fi ;; *) AC_PATH_PROG([PerlCmd],[perl]) @@ -1258,8 +1297,8 @@ echo "\ libtool : $LibtoolCmd objdump : $ObjdumpCmd ranlib : $RanlibCmd - windres : $Windres - dllwrap : $DllWrap + windres : $WindresCmd + dllwrap : $DllWrapCmd Happy : $HappyCmd ($HappyVersion) Alex : $AlexCmd ($AlexVersion) Perl : $PerlCmd diff --git a/docs/users_guide/8.4.1-notes.rst b/docs/users_guide/8.4.1-notes.rst index 5929998..f23cb36 100644 --- a/docs/users_guide/8.4.1-notes.rst +++ b/docs/users_guide/8.4.1-notes.rst @@ -76,6 +76,10 @@ Now we generate :: _ == _ = error ... +- Configure on Windows now supports ``--enable-distro-toolchain`` which can be + used to build a GHC using compilers on your ``PATH`` instead of using the + bundled bindist. See :ghc-ticket:`13792` + - Lots of other bugs. See `Trac `_ for a complete list. From git at git.haskell.org Sat Jun 17 00:17:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 00:17:19 +0000 (UTC) Subject: [commit: ghc] master: Remove the Windows GCC driver. (d6cecde) Message-ID: <20170617001719.C7D6C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d6cecde585b0980ed8e0050c5a1d315789fb6356/ghc >--------------------------------------------------------------- commit d6cecde585b0980ed8e0050c5a1d315789fb6356 Author: Tamar Christina Date: Sat Jun 17 01:05:52 2017 +0100 Remove the Windows GCC driver. Summary: This patch drops the GCC driver and instead moves the only remaining path that we need to keep for backwards compatibility to the settings file. It also generalizes the code that expands `$TopDir` so it can expand it within any location in the string and also changes it so `$TopDir` is expanded only after the words call because `$TopDir` can contains spaces which would be horribly broken. Test Plan: ./validate Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, erikd GHC Trac Issues: #13709 Differential Revision: https://phabricator.haskell.org/D3592 >--------------------------------------------------------------- d6cecde585b0980ed8e0050c5a1d315789fb6356 aclocal.m4 | 3 +- compiler/main/SysTools.hs | 38 +++++++++++++++-------- configure.ac | 8 ----- docs/users_guide/8.4.1-notes.rst | 3 ++ driver/gcc/gcc.c | 66 ---------------------------------------- 5 files changed, 30 insertions(+), 88 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d6cecde585b0980ed8e0050c5a1d315789fb6356 From git at git.haskell.org Sat Jun 17 13:49:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:49:43 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Reformat (518bb35) Message-ID: <20170617134943.89E633A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/518bb35c07a85d2f75263c93e1833e136ad608d7/ghc >--------------------------------------------------------------- commit 518bb35c07a85d2f75263c93e1833e136ad608d7 Author: Ben Gamari Date: Thu May 18 02:58:05 2017 -0400 Reformat >--------------------------------------------------------------- 518bb35c07a85d2f75263c93e1833e136ad608d7 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 Sat Jun 17 13:49:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:49:46 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Testing (8d0dbf7) Message-ID: <20170617134946.4F1C23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/8d0dbf74622306411f41ad7c50045816a2fd7d11/ghc >--------------------------------------------------------------- commit 8d0dbf74622306411f41ad7c50045816a2fd7d11 Author: Ben Gamari Date: Fri Apr 28 09:53:13 2017 -0400 Testing >--------------------------------------------------------------- 8d0dbf74622306411f41ad7c50045816a2fd7d11 Jenkinsfile | 30 +++++++++++++++++------------- 1 file changed, 17 insertions(+), 13 deletions(-) diff --git a/Jenkinsfile b/Jenkinsfile index 7ff08f0..f643e51 100644 --- a/Jenkinsfile +++ b/Jenkinsfile @@ -1,16 +1,20 @@ pipeline { - agent any - stages { - stage('Build') { - steps { - sh 'git submodule update --init --recursive' - sh ''' - ./boot - ./configure --enable-tarballs-autodownload - make -j$THREADS - make THREADS=$THREADS test - ''' - } - } + agent any + parameters { + booleanParam(name: 'build_docs', defaultValue: false, description: 'build and upload documentation') + } + + stages { + stage('Build') { + steps { + sh 'git submodule update --init --recursive' + sh ''' + ./boot + ./configure --enable-tarballs-autodownload + make -j$THREADS + make THREADS=$THREADS test + ''' + } } + } } From git at git.haskell.org Sat Jun 17 13:49:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:49:49 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (ad6bb58) Message-ID: <20170617134949.060463A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ad6bb5807d64a59cf936d7c728b6fe3890a447e9/ghc >--------------------------------------------------------------- commit ad6bb5807d64a59cf936d7c728b6fe3890a447e9 Author: Ben Gamari Date: Thu May 18 02:56:06 2017 -0400 Debug >--------------------------------------------------------------- ad6bb5807d64a59cf936d7c728b6fe3890a447e9 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 Sat Jun 17 13:49:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:49:51 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Try again (846f1c9) Message-ID: <20170617134951.B2E5D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/846f1c9fce258ab0514bcc149e4308245f7b2b20/ghc >--------------------------------------------------------------- commit 846f1c9fce258ab0514bcc149e4308245f7b2b20 Author: Ben Gamari Date: Mon May 29 16:42:42 2017 -0400 Try again >--------------------------------------------------------------- 846f1c9fce258ab0514bcc149e4308245f7b2b20 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 Sat Jun 17 13:49:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:49:57 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (66fe057) Message-ID: <20170617134957.3062D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/66fe0575d570eaf66c4de461bdbf02ee3522ca6f/ghc >--------------------------------------------------------------- commit 66fe0575d570eaf66c4de461bdbf02ee3522ca6f Author: Ben Gamari Date: Wed May 17 23:42:59 2017 -0400 Debug >--------------------------------------------------------------- 66fe0575d570eaf66c4de461bdbf02ee3522ca6f 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 Sat Jun 17 13:50:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:02 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Introduce echo! make target (2824fcf) Message-ID: <20170617135002.98BDA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2824fcf453d99df16076117ab19e490fe738629b/ghc >--------------------------------------------------------------- commit 2824fcf453d99df16076117ab19e490fe738629b Author: Ben Gamari Date: Sun Jun 4 10:27:24 2017 -0400 Introduce echo! make target This is analogous to show! >--------------------------------------------------------------- 2824fcf453d99df16076117ab19e490fe738629b 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 3fafcf0..dd9d8b6 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 Sat Jun 17 13:50:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:05 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix documentation (7f7897d) Message-ID: <20170617135005.4D8533A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7f7897da699766854e8d0942c7c40f502ea4c6be/ghc >--------------------------------------------------------------- commit 7f7897da699766854e8d0942c7c40f502ea4c6be Author: Ben Gamari Date: Tue May 30 10:45:52 2017 -0400 Fix documentation >--------------------------------------------------------------- 7f7897da699766854e8d0942c7c40f502ea4c6be 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 Sat Jun 17 13:49:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:49:59 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Handle documentation (d0a53b6) Message-ID: <20170617134959.DDC483A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d0a53b6695d572e2014de552606e97963c050e6f/ghc >--------------------------------------------------------------- commit d0a53b6695d572e2014de552606e97963c050e6f Author: Ben Gamari Date: Tue May 30 01:46:06 2017 -0400 Handle documentation >--------------------------------------------------------------- d0a53b6695d572e2014de552606e97963c050e6f 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 Sat Jun 17 13:49:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:49:54 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Clean up treatment of tests (7fc463a) Message-ID: <20170617134954.71B983A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7fc463a626998e6a9081ba52b6d633a966eefdc3/ghc >--------------------------------------------------------------- commit 7fc463a626998e6a9081ba52b6d633a966eefdc3 Author: Ben Gamari Date: Tue May 30 01:10:56 2017 -0400 Clean up treatment of tests >--------------------------------------------------------------- 7fc463a626998e6a9081ba52b6d633a966eefdc3 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 Sat Jun 17 13:50:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:08 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarball generation (cdd2988) Message-ID: <20170617135008.0746A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/cdd29883fae2fc21567280f0a734923289080056/ghc >--------------------------------------------------------------- commit cdd29883fae2fc21567280f0a734923289080056 Author: Ben Gamari Date: Tue May 30 10:43:09 2017 -0400 Fix tarball generation >--------------------------------------------------------------- cdd29883fae2fc21567280f0a734923289080056 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 Sat Jun 17 13:50:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:10 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Unregisterised (f7fa958) Message-ID: <20170617135010.B2A723A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/f7fa9588ff5347d9de343062b6c043aca8dbc11d/ghc >--------------------------------------------------------------- commit f7fa9588ff5347d9de343062b6c043aca8dbc11d Author: Ben Gamari Date: Thu May 18 01:55:35 2017 -0400 Unregisterised >--------------------------------------------------------------- f7fa9588ff5347d9de343062b6c043aca8dbc11d 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 Sat Jun 17 13:50:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:13 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring, add Windows, fix cross (002ba52) Message-ID: <20170617135013.68DDC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/002ba5215ab5ff9b1af656a1bdbceac9565b258b/ghc >--------------------------------------------------------------- commit 002ba5215ab5ff9b1af656a1bdbceac9565b258b Author: Ben Gamari Date: Thu May 18 02:14:40 2017 -0400 Refactoring, add Windows, fix cross >--------------------------------------------------------------- 002ba5215ab5ff9b1af656a1bdbceac9565b258b 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 Sat Jun 17 13:50:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:16 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix testsuite (c6e8ea1) Message-ID: <20170617135016.20F403A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c6e8ea1509724c18a9e136b9dedede30855cfe43/ghc >--------------------------------------------------------------- commit c6e8ea1509724c18a9e136b9dedede30855cfe43 Author: Ben Gamari Date: Tue May 30 12:11:16 2017 -0400 Fix testsuite >--------------------------------------------------------------- c6e8ea1509724c18a9e136b9dedede30855cfe43 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 Sat Jun 17 13:50:18 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:18 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Hmm (9a5b253) Message-ID: <20170617135018.C9C883A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9a5b25383752b82e6068014be74c3350053126d1/ghc >--------------------------------------------------------------- commit 9a5b25383752b82e6068014be74c3350053126d1 Author: Ben Gamari Date: Mon May 29 16:45:16 2017 -0400 Hmm >--------------------------------------------------------------- 9a5b25383752b82e6068014be74c3350053126d1 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 Sat Jun 17 13:50:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:21 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Don't run nofib on Windows (518a45e) Message-ID: <20170617135021.83A013A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/518a45efdebe934c9db1a35d42ddfddb223cc66d/ghc >--------------------------------------------------------------- commit 518a45efdebe934c9db1a35d42ddfddb223cc66d Author: Ben Gamari Date: Mon May 29 16:14:11 2017 -0400 Don't run nofib on Windows >--------------------------------------------------------------- 518a45efdebe934c9db1a35d42ddfddb223cc66d 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 Sat Jun 17 13:50:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:24 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarball names (2102abe) Message-ID: <20170617135024.3BD763A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2102abe8839dca1d37f1ca07884b236e5bc152dd/ghc >--------------------------------------------------------------- commit 2102abe8839dca1d37f1ca07884b236e5bc152dd Author: Ben Gamari Date: Sun Jun 4 10:34:37 2017 -0400 Fix tarball names >--------------------------------------------------------------- 2102abe8839dca1d37f1ca07884b236e5bc152dd 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 Sat Jun 17 13:50:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:26 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Kill debugging (da11119) Message-ID: <20170617135026.E89923A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/da11119b7f1a9fef952ca5049bfa4b6bd4e2a287/ghc >--------------------------------------------------------------- commit da11119b7f1a9fef952ca5049bfa4b6bd4e2a287 Author: Ben Gamari Date: Thu May 18 01:39:32 2017 -0400 Kill debugging >--------------------------------------------------------------- da11119b7f1a9fef952ca5049bfa4b6bd4e2a287 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 Sat Jun 17 13:50:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:32 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix missing binding (3661177) Message-ID: <20170617135032.57F4E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/366117780caf9f2430bf66c4c907402412d20210/ghc >--------------------------------------------------------------- commit 366117780caf9f2430bf66c4c907402412d20210 Author: Ben Gamari Date: Wed May 31 11:36:00 2017 -0400 Fix missing binding >--------------------------------------------------------------- 366117780caf9f2430bf66c4c907402412d20210 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 Sat Jun 17 13:50:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:29 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Disable non-Windows builds (d5ef4ed) Message-ID: <20170617135029.A00213A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d5ef4ed6c6afea0d668818f7806c4d2c368c653f/ghc >--------------------------------------------------------------- commit d5ef4ed6c6afea0d668818f7806c4d2c368c653f Author: Ben Gamari Date: Mon May 29 19:34:11 2017 -0400 Disable non-Windows builds >--------------------------------------------------------------- d5ef4ed6c6afea0d668818f7806c4d2c368c653f 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 Sat Jun 17 13:50:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:35 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Disable large address space on FreeBSD (7601ad8) Message-ID: <20170617135035.19FF13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7601ad8f59619a746a3df0f92b9ca1b79b5b4511/ghc >--------------------------------------------------------------- commit 7601ad8f59619a746a3df0f92b9ca1b79b5b4511 Author: Ben Gamari Date: Mon May 29 16:34:26 2017 -0400 Disable large address space on FreeBSD >--------------------------------------------------------------- 7601ad8f59619a746a3df0f92b9ca1b79b5b4511 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 Sat Jun 17 13:50:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:37 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix JSON serialization (e8318c4) Message-ID: <20170617135037.C66FF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/e8318c4a54392d6ad5bb4782117b9828c37beeb3/ghc >--------------------------------------------------------------- commit e8318c4a54392d6ad5bb4782117b9828c37beeb3 Author: Ben Gamari Date: Wed May 31 10:43:24 2017 -0400 Fix JSON serialization >--------------------------------------------------------------- e8318c4a54392d6ad5bb4782117b9828c37beeb3 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 Sat Jun 17 13:50:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:41 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Testing simpler Jenkinsfile (7208e5e) Message-ID: <20170617135041.062373A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7208e5e5950e534e0c0a0e01f641b27f86ae913e/ghc >--------------------------------------------------------------- commit 7208e5e5950e534e0c0a0e01f641b27f86ae913e Author: Ben Gamari Date: Fri Apr 21 14:29:34 2017 -0400 Testing simpler Jenkinsfile >--------------------------------------------------------------- 7208e5e5950e534e0c0a0e01f641b27f86ae913e Jenkinsfile | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) diff --git a/Jenkinsfile b/Jenkinsfile new file mode 100644 index 0000000..7ff08f0 --- /dev/null +++ b/Jenkinsfile @@ -0,0 +1,16 @@ +pipeline { + agent any + stages { + stage('Build') { + steps { + sh 'git submodule update --init --recursive' + sh ''' + ./boot + ./configure --enable-tarballs-autodownload + make -j$THREADS + make THREADS=$THREADS test + ''' + } + } + } +} From git at git.haskell.org Sat Jun 17 13:50:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:43 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Checkout (d5e2a48) Message-ID: <20170617135043.B48483A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d5e2a483b1e9e6217053cfd761bdb02610d81496/ghc >--------------------------------------------------------------- commit d5e2a483b1e9e6217053cfd761bdb02610d81496 Author: Ben Gamari Date: Thu May 18 01:19:52 2017 -0400 Checkout >--------------------------------------------------------------- d5e2a483b1e9e6217053cfd761bdb02610d81496 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 Sat Jun 17 13:50:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:46 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Cross (7daefcf) Message-ID: <20170617135046.6CA543A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7daefcf697f3c0a3b8aa3a50d7695df0c90634f6/ghc >--------------------------------------------------------------- commit 7daefcf697f3c0a3b8aa3a50d7695df0c90634f6 Author: Ben Gamari Date: Thu May 18 01:00:42 2017 -0400 Cross >--------------------------------------------------------------- 7daefcf697f3c0a3b8aa3a50d7695df0c90634f6 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 Sat Jun 17 13:50:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:49 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix Windows PATHs (9e7a054) Message-ID: <20170617135049.2616E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9e7a054ed827b41b714c470bf0473e2b04a1fcd9/ghc >--------------------------------------------------------------- commit 9e7a054ed827b41b714c470bf0473e2b04a1fcd9 Author: Ben Gamari Date: Mon May 29 16:31:28 2017 -0400 Fix Windows PATHs >--------------------------------------------------------------- 9e7a054ed827b41b714c470bf0473e2b04a1fcd9 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 Sat Jun 17 13:50:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:51 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rework handling of Windows (54c2269) Message-ID: <20170617135051.D721A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/54c226979875c4952e4dc4fc1dad794adb8d4983/ghc >--------------------------------------------------------------- commit 54c226979875c4952e4dc4fc1dad794adb8d4983 Author: Ben Gamari Date: Mon May 29 13:08:49 2017 -0400 Rework handling of Windows >--------------------------------------------------------------- 54c226979875c4952e4dc4fc1dad794adb8d4983 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 Sat Jun 17 13:50:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:54 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (a6f6544) Message-ID: <20170617135054.8DBBB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a6f654480085aec814977c8eda58a6761c648a24/ghc >--------------------------------------------------------------- commit a6f654480085aec814977c8eda58a6761c648a24 Author: Ben Gamari Date: Wed May 31 14:57:34 2017 -0400 Debug >--------------------------------------------------------------- a6f654480085aec814977c8eda58a6761c648a24 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 Sat Jun 17 13:50:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:57 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Run jobs in parallel (70c98a6) Message-ID: <20170617135057.42E303A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/70c98a691d74976babd84f69e0e611a464daaee4/ghc >--------------------------------------------------------------- commit 70c98a691d74976babd84f69e0e611a464daaee4 Author: Ben Gamari Date: Wed May 17 23:34:37 2017 -0400 Run jobs in parallel >--------------------------------------------------------------- 70c98a691d74976babd84f69e0e611a464daaee4 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 Sat Jun 17 13:50:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:50:59 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: More things (e29b4ff) Message-ID: <20170617135059.EC7543A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/e29b4ff4c6e28d1db31b6b651d722c8e3fc3d101/ghc >--------------------------------------------------------------- commit e29b4ff4c6e28d1db31b6b651d722c8e3fc3d101 Author: Ben Gamari Date: Thu May 18 01:38:55 2017 -0400 More things >--------------------------------------------------------------- e29b4ff4c6e28d1db31b6b651d722c8e3fc3d101 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 Sat Jun 17 13:51:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:02 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix test (27130fb) Message-ID: <20170617135102.A7D533A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/27130fb555b4cbb125e468f4edbfb7bfe15f7356/ghc >--------------------------------------------------------------- commit 27130fb555b4cbb125e468f4edbfb7bfe15f7356 Author: Ben Gamari Date: Tue May 30 13:57:23 2017 -0400 Fix test >--------------------------------------------------------------- 27130fb555b4cbb125e468f4edbfb7bfe15f7356 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 Sat Jun 17 13:51:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:05 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Reenable everything else (44bc035) Message-ID: <20170617135105.696103A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/44bc035e56c09bafea61d7ded8eadd6bd0913ead/ghc >--------------------------------------------------------------- commit 44bc035e56c09bafea61d7ded8eadd6bd0913ead Author: Ben Gamari Date: Mon May 29 22:45:19 2017 -0400 Reenable everything else >--------------------------------------------------------------- 44bc035e56c09bafea61d7ded8eadd6bd0913ead 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 Sat Jun 17 13:51:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:08 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Refactoring (4b9e062) Message-ID: <20170617135108.25D863A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/4b9e06259f012cd5f250f4c485ff5612b85e6a3d/ghc >--------------------------------------------------------------- commit 4b9e06259f012cd5f250f4c485ff5612b85e6a3d Author: Ben Gamari Date: Wed May 17 20:20:55 2017 -0400 Refactoring >--------------------------------------------------------------- 4b9e06259f012cd5f250f4c485ff5612b85e6a3d 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 Sat Jun 17 13:51:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:10 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Build from source distribution (8ed117a) Message-ID: <20170617135110.D28CB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/8ed117a4e0fb3127505325ee6791599e6bf76a4f/ghc >--------------------------------------------------------------- commit 8ed117a4e0fb3127505325ee6791599e6bf76a4f Author: Ben Gamari Date: Mon May 29 13:55:58 2017 -0400 Build from source distribution >--------------------------------------------------------------- 8ed117a4e0fb3127505325ee6791599e6bf76a4f 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 Sat Jun 17 13:51:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:13 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: windows (97e88fa) Message-ID: <20170617135113.972363A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/97e88fab23153d69975b02f85f08117ee4b5aa4f/ghc >--------------------------------------------------------------- commit 97e88fab23153d69975b02f85f08117ee4b5aa4f Author: Ben Gamari Date: Thu May 18 01:55:46 2017 -0400 windows >--------------------------------------------------------------- 97e88fab23153d69975b02f85f08117ee4b5aa4f 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 Sat Jun 17 13:51:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:16 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Parametrize on make command (adee5ed) Message-ID: <20170617135116.52B073A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/adee5edb08cee9829d74e4eae733ef881a5d80d6/ghc >--------------------------------------------------------------- commit adee5edb08cee9829d74e4eae733ef881a5d80d6 Author: Ben Gamari Date: Mon May 29 15:44:39 2017 -0400 Parametrize on make command >--------------------------------------------------------------- adee5edb08cee9829d74e4eae733ef881a5d80d6 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 Sat Jun 17 13:51:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:19 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix configure arguments (0b0f156) Message-ID: <20170617135119.11F923A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0b0f15621d40ee140636b7b0d4787be2e2b92335/ghc >--------------------------------------------------------------- commit 0b0f15621d40ee140636b7b0d4787be2e2b92335 Author: Ben Gamari Date: Mon May 29 22:55:51 2017 -0400 Fix configure arguments >--------------------------------------------------------------- 0b0f15621d40ee140636b7b0d4787be2e2b92335 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 Sat Jun 17 13:51:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:21 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Use archiveArtifacts instead of archive (d6e5547) Message-ID: <20170617135121.BEA413A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d6e5547daf6202dd54d4dfcd765a784c3010305b/ghc >--------------------------------------------------------------- commit d6e5547daf6202dd54d4dfcd765a784c3010305b Author: Ben Gamari Date: Mon May 29 15:44:56 2017 -0400 Use archiveArtifacts instead of archive >--------------------------------------------------------------- d6e5547daf6202dd54d4dfcd765a784c3010305b 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 Sat Jun 17 13:51:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:24 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (6b555e0) Message-ID: <20170617135124.802ED3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/6b555e0366fd7467015c4eb27f6a64a0ec72e1d7/ghc >--------------------------------------------------------------- commit 6b555e0366fd7467015c4eb27f6a64a0ec72e1d7 Author: Ben Gamari Date: Mon May 29 15:49:33 2017 -0400 Debug >--------------------------------------------------------------- 6b555e0366fd7467015c4eb27f6a64a0ec72e1d7 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 Sat Jun 17 13:51:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:27 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Actually call closure (0aaf511) Message-ID: <20170617135127.3A92E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0aaf51103fbfb5dd671e5770267e4090dd8eac88/ghc >--------------------------------------------------------------- commit 0aaf51103fbfb5dd671e5770267e4090dd8eac88 Author: Ben Gamari Date: Sun Jun 4 01:02:20 2017 -0400 Actually call closure >--------------------------------------------------------------- 0aaf51103fbfb5dd671e5770267e4090dd8eac88 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 Sat Jun 17 13:51:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:29 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (e4dd926) Message-ID: <20170617135129.E67353A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/e4dd9263241c41b056e01e183d9521ed7bf258e5/ghc >--------------------------------------------------------------- commit e4dd9263241c41b056e01e183d9521ed7bf258e5 Author: Ben Gamari Date: Thu May 18 02:59:40 2017 -0400 Debug >--------------------------------------------------------------- e4dd9263241c41b056e01e183d9521ed7bf258e5 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 Sat Jun 17 13:51:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:32 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Clean (85895bc) Message-ID: <20170617135132.A05EE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/85895bcb09b45ace09f815be1910d93938828f90/ghc >--------------------------------------------------------------- commit 85895bcb09b45ace09f815be1910d93938828f90 Author: Ben Gamari Date: Tue May 30 00:29:29 2017 -0400 Clean >--------------------------------------------------------------- 85895bcb09b45ace09f815be1910d93938828f90 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 Sat Jun 17 13:51:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:35 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Move to scripted pipeline (3519604) Message-ID: <20170617135135.62CE23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/3519604f2fb3b6ccca4176fca3940ab068bd94a2/ghc >--------------------------------------------------------------- commit 3519604f2fb3b6ccca4176fca3940ab068bd94a2 Author: Ben Gamari Date: Wed May 17 20:52:58 2017 -0400 Move to scripted pipeline >--------------------------------------------------------------- 3519604f2fb3b6ccca4176fca3940ab068bd94a2 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 Sat Jun 17 13:51:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:38 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: More debugging (50d7176) Message-ID: <20170617135138.2030A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/50d71769c98b5ccbe86645733baf3713eab5fec4/ghc >--------------------------------------------------------------- commit 50d71769c98b5ccbe86645733baf3713eab5fec4 Author: Ben Gamari Date: Sat Jun 3 17:02:01 2017 -0400 More debugging >--------------------------------------------------------------- 50d71769c98b5ccbe86645733baf3713eab5fec4 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 Sat Jun 17 13:51:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:40 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Hopefully fix Windows (61fa6ff) Message-ID: <20170617135140.CF3473A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/61fa6ff3f158f734b908fcce5dee903867dcd550/ghc >--------------------------------------------------------------- commit 61fa6ff3f158f734b908fcce5dee903867dcd550 Author: Ben Gamari Date: Mon May 29 22:33:46 2017 -0400 Hopefully fix Windows >--------------------------------------------------------------- 61fa6ff3f158f734b908fcce5dee903867dcd550 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 Sat Jun 17 13:51:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:43 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add THREADS parameter (376307d) Message-ID: <20170617135143.8FDB13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/376307d96773bc21f971bc4e41792bc79492f26f/ghc >--------------------------------------------------------------- commit 376307d96773bc21f971bc4e41792bc79492f26f Author: Ben Gamari Date: Sat May 13 11:59:37 2017 -0400 Add THREADS parameter >--------------------------------------------------------------- 376307d96773bc21f971bc4e41792bc79492f26f 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 Sat Jun 17 13:51:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:46 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Be more explicit (94e6a82) Message-ID: <20170617135146.4A6953A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/94e6a82734a3b044f23896f32ae3cad0d3e3e516/ghc >--------------------------------------------------------------- commit 94e6a82734a3b044f23896f32ae3cad0d3e3e516 Author: Ben Gamari Date: Tue May 30 16:04:31 2017 -0400 Be more explicit >--------------------------------------------------------------- 94e6a82734a3b044f23896f32ae3cad0d3e3e516 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 Sat Jun 17 13:51:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:49 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix FreeBSD architecture (5181ed1) Message-ID: <20170617135149.016F03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/5181ed195a6628b50c2c86ce960c51a41d29e26e/ghc >--------------------------------------------------------------- commit 5181ed195a6628b50c2c86ce960c51a41d29e26e Author: Ben Gamari Date: Mon May 29 13:55:03 2017 -0400 Fix FreeBSD architecture >--------------------------------------------------------------- 5181ed195a6628b50c2c86ce960c51a41d29e26e 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 Sat Jun 17 13:51:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:51 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Nailed the Windows issue (01dd168) Message-ID: <20170617135151.B7A763A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/01dd168f196e2df4b430b474a97a807df79a4698/ghc >--------------------------------------------------------------- commit 01dd168f196e2df4b430b474a97a807df79a4698 Author: Ben Gamari Date: Mon May 29 12:48:34 2017 -0400 Nailed the Windows issue >--------------------------------------------------------------- 01dd168f196e2df4b430b474a97a807df79a4698 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 Sat Jun 17 13:51:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:54 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix tarName (0b5a27c) Message-ID: <20170617135154.6E50E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0b5a27cb0577af74311c01abd61180ec97b516fe/ghc >--------------------------------------------------------------- commit 0b5a27cb0577af74311c01abd61180ec97b516fe Author: Ben Gamari Date: Sat Jun 3 21:33:12 2017 -0400 Fix tarName >--------------------------------------------------------------- 0b5a27cb0577af74311c01abd61180ec97b516fe 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 Sat Jun 17 13:51:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:57 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Add nofib, bindist, and aarch64 support (a67c52a) Message-ID: <20170617135157.2A5943A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a67c52a45ad5d719e1f60fb26017bd68b184f224/ghc >--------------------------------------------------------------- commit a67c52a45ad5d719e1f60fb26017bd68b184f224 Author: Ben Gamari Date: Wed May 17 22:41:02 2017 -0400 Add nofib, bindist, and aarch64 support >--------------------------------------------------------------- a67c52a45ad5d719e1f60fb26017bd68b184f224 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 Sat Jun 17 13:51:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:51:59 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: A bit more paranoia around directory deletion (ba840ee) Message-ID: <20170617135159.E41E73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ba840ee72d781384201f0ff91aa67c26127007e0/ghc >--------------------------------------------------------------- commit ba840ee72d781384201f0ff91aa67c26127007e0 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. >--------------------------------------------------------------- ba840ee72d781384201f0ff91aa67c26127007e0 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 Sat Jun 17 13:52:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:02 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Show location of stage0 compiler (57ca8ee) Message-ID: <20170617135202.A4CCE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/57ca8ee3fd301b5ee3b059469ee9bbedf33b7908/ghc >--------------------------------------------------------------- commit 57ca8ee3fd301b5ee3b059469ee9bbedf33b7908 Author: Ben Gamari Date: Tue Jun 13 16:10:23 2017 -0400 Show location of stage0 compiler >--------------------------------------------------------------- 57ca8ee3fd301b5ee3b059469ee9bbedf33b7908 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 Sat Jun 17 13:52:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:05 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Use named argument list (99d5b24) Message-ID: <20170617135205.79CA63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/99d5b24f79f17e3ac757ababca46a537d2dfc4e9/ghc >--------------------------------------------------------------- commit 99d5b24f79f17e3ac757ababca46a537d2dfc4e9 Author: Ben Gamari Date: Mon Jun 5 13:27:27 2017 -0400 Use named argument list >--------------------------------------------------------------- 99d5b24f79f17e3ac757ababca46a537d2dfc4e9 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 Sat Jun 17 13:52:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:08 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix binding name (964bce4) Message-ID: <20170617135208.37BF23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/964bce4f394ba89667d3c2ea92a134aeb39201ea/ghc >--------------------------------------------------------------- commit 964bce4f394ba89667d3c2ea92a134aeb39201ea Author: Ben Gamari Date: Mon Jun 12 22:25:11 2017 -0400 Fix binding name >--------------------------------------------------------------- 964bce4f394ba89667d3c2ea92a134aeb39201ea 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 Sat Jun 17 13:52:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:10 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Run stage1 tests as well (8dda9de) Message-ID: <20170617135210.ED1853A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/8dda9defb8637980a545571eb67f20716a55cf10/ghc >--------------------------------------------------------------- commit 8dda9defb8637980a545571eb67f20716a55cf10 Author: Ben Gamari Date: Sun Jun 4 21:24:15 2017 -0400 Run stage1 tests as well >--------------------------------------------------------------- 8dda9defb8637980a545571eb67f20716a55cf10 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 Sat Jun 17 13:52:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:13 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rip out debug output (b304042) Message-ID: <20170617135213.ABAF53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/b304042d5d95abb14e15fcc555f8d9f834b9ebb2/ghc >--------------------------------------------------------------- commit b304042d5d95abb14e15fcc555f8d9f834b9ebb2 Author: Ben Gamari Date: Sun Jun 4 11:36:21 2017 -0400 Rip out debug output >--------------------------------------------------------------- b304042d5d95abb14e15fcc555f8d9f834b9ebb2 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 Sat Jun 17 13:52:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:16 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Don't try to record commit of bindist (c6d0f870) Message-ID: <20170617135216.63DE93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/c6d0f870779bdff04b5def72c0ab6b2046fd573b/ghc >--------------------------------------------------------------- commit c6d0f870779bdff04b5def72c0ab6b2046fd573b Author: Ben Gamari Date: Mon Jun 5 15:31:26 2017 -0400 Don't try to record commit of bindist >--------------------------------------------------------------- c6d0f870779bdff04b5def72c0ab6b2046fd573b 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 Sat Jun 17 13:52:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:19 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (e8ffc6d) Message-ID: <20170617135219.1B8A73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/e8ffc6d2b9b3a6433020de3d8df45e9b5c337712/ghc >--------------------------------------------------------------- commit e8ffc6d2b9b3a6433020de3d8df45e9b5c337712 Author: Ben Gamari Date: Sun Jun 4 11:18:23 2017 -0400 Debug >--------------------------------------------------------------- e8ffc6d2b9b3a6433020de3d8df45e9b5c337712 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 Sat Jun 17 13:52:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:21 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Ensure that carch, prefix, and ghcPath are in scope (6bb51f8) Message-ID: <20170617135221.CE8993A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/6bb51f89266ff75c218da64ac2ee3e16b3c70fe7/ghc >--------------------------------------------------------------- commit 6bb51f89266ff75c218da64ac2ee3e16b3c70fe7 Author: Ben Gamari Date: Mon Jun 12 16:31:31 2017 -0400 Ensure that carch, prefix, and ghcPath are in scope >--------------------------------------------------------------- 6bb51f89266ff75c218da64ac2ee3e16b3c70fe7 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 Sat Jun 17 13:52:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:24 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Try adding type annotation (aefb586) Message-ID: <20170617135224.899993A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/aefb586dd15f249858b678f9618f49da1261a70b/ghc >--------------------------------------------------------------- commit aefb586dd15f249858b678f9618f49da1261a70b Author: Ben Gamari Date: Sun Jun 4 11:26:54 2017 -0400 Try adding type annotation >--------------------------------------------------------------- aefb586dd15f249858b678f9618f49da1261a70b 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 Sat Jun 17 13:52:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:27 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix source directory name (3a2dd88) Message-ID: <20170617135227.4A1D53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/3a2dd88d7ab9ef5f8eea27755bfc9760c9f7a846/ghc >--------------------------------------------------------------- commit 3a2dd88d7ab9ef5f8eea27755bfc9760c9f7a846 Author: Ben Gamari Date: Sun Jun 4 11:06:15 2017 -0400 Fix source directory name >--------------------------------------------------------------- 3a2dd88d7ab9ef5f8eea27755bfc9760c9f7a846 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 Sat Jun 17 13:52:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:30 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: No need to boot (82839e9) Message-ID: <20170617135230.045BB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/82839e909445f6afce5ecd728765280b99df1188/ghc >--------------------------------------------------------------- commit 82839e909445f6afce5ecd728765280b99df1188 Author: Ben Gamari Date: Sun Jun 4 10:54:49 2017 -0400 No need to boot >--------------------------------------------------------------- 82839e909445f6afce5ecd728765280b99df1188 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 Sat Jun 17 13:52:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:32 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Pass BINDIST to make test (6fb1f3b) Message-ID: <20170617135232.B624E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/6fb1f3b01ccba86006dad1ba24b350fa969afe62/ghc >--------------------------------------------------------------- commit 6fb1f3b01ccba86006dad1ba24b350fa969afe62 Author: Ben Gamari Date: Mon Jun 5 13:15:45 2017 -0400 Pass BINDIST to make test >--------------------------------------------------------------- 6fb1f3b01ccba86006dad1ba24b350fa969afe62 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 Sat Jun 17 13:52:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:35 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debug (9b034ea) Message-ID: <20170617135235.8D2B63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9b034ead3fe03c1bb9717b50ef7df9e73ea7bbf6/ghc >--------------------------------------------------------------- commit 9b034ead3fe03c1bb9717b50ef7df9e73ea7bbf6 Author: Ben Gamari Date: Sun Jun 4 11:32:08 2017 -0400 Debug >--------------------------------------------------------------- 9b034ead3fe03c1bb9717b50ef7df9e73ea7bbf6 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 Sat Jun 17 13:52:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:38 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix quoting of carch (d1a5dcd) Message-ID: <20170617135238.4A43D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/d1a5dcd26d0003455ceba41d55675083958d392f/ghc >--------------------------------------------------------------- commit d1a5dcd26d0003455ceba41d55675083958d392f Author: Ben Gamari Date: Mon Jun 12 16:40:33 2017 -0400 Fix quoting of carch >--------------------------------------------------------------- d1a5dcd26d0003455ceba41d55675083958d392f 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 Sat Jun 17 13:52:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:41 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Rework handling of nofib (0f274af) Message-ID: <20170617135241.0F3573A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/0f274afb02decbcccbd254a3b017522f1bade1d2/ghc >--------------------------------------------------------------- commit 0f274afb02decbcccbd254a3b017522f1bade1d2 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. >--------------------------------------------------------------- 0f274afb02decbcccbd254a3b017522f1bade1d2 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 Sat Jun 17 13:52:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:43 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: debugging (6aa4332) Message-ID: <20170617135243.DB0A13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/6aa4332977c6865e673b3fe8ef85a6c80659bb87/ghc >--------------------------------------------------------------- commit 6aa4332977c6865e673b3fe8ef85a6c80659bb87 Author: Ben Gamari Date: Fri Jun 16 14:31:43 2017 -0400 debugging >--------------------------------------------------------------- 6aa4332977c6865e673b3fe8ef85a6c80659bb87 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 Sat Jun 17 13:52:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:46 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: No need to configure (857fa03) Message-ID: <20170617135246.937063A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/857fa0330b91d4dd8ac800196525fe3cf7d8ede5/ghc >--------------------------------------------------------------- commit 857fa0330b91d4dd8ac800196525fe3cf7d8ede5 Author: Ben Gamari Date: Sun Jun 4 10:47:30 2017 -0400 No need to configure >--------------------------------------------------------------- 857fa0330b91d4dd8ac800196525fe3cf7d8ede5 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 Sat Jun 17 13:52:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:52 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Kill debug output (11cf82f) Message-ID: <20170617135252.0FC3C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/11cf82f02770e76ee729bc9fe5e65b78b1238fbb/ghc >--------------------------------------------------------------- commit 11cf82f02770e76ee729bc9fe5e65b78b1238fbb Author: Ben Gamari Date: Wed Jun 14 16:55:46 2017 -0400 Kill debug output >--------------------------------------------------------------- 11cf82f02770e76ee729bc9fe5e65b78b1238fbb 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 Sat Jun 17 13:52:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:49 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix GHC path (5798eb1) Message-ID: <20170617135249.57C2D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/5798eb1e24aca5d02089a521161dfe0d6b90d797/ghc >--------------------------------------------------------------- commit 5798eb1e24aca5d02089a521161dfe0d6b90d797 Author: Ben Gamari Date: Tue Jun 13 00:44:15 2017 -0400 Fix GHC path >--------------------------------------------------------------- 5798eb1e24aca5d02089a521161dfe0d6b90d797 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 Sat Jun 17 13:52:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:54 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Debuggging (bb43c66) Message-ID: <20170617135254.B9E643A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/bb43c66bf22ef1818986d9d379feebda8bf7e2af/ghc >--------------------------------------------------------------- commit bb43c66bf22ef1818986d9d379feebda8bf7e2af Author: Ben Gamari Date: Sun Jun 4 11:12:23 2017 -0400 Debuggging >--------------------------------------------------------------- bb43c66bf22ef1818986d9d379feebda8bf7e2af 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 Sat Jun 17 13:52:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:52:57 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Configure bindist (ffecf49) Message-ID: <20170617135257.743CC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ffecf490170da847a6eec833442e95746959e119/ghc >--------------------------------------------------------------- commit ffecf490170da847a6eec833442e95746959e119 Author: Ben Gamari Date: Sun Jun 4 12:32:40 2017 -0400 Configure bindist >--------------------------------------------------------------- ffecf490170da847a6eec833442e95746959e119 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 Sat Jun 17 13:53:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:53:00 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Archive source distribution (a887c5c) Message-ID: <20170617135300.3974A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/a887c5c8240fcdb3f0b1b9bd6c892787dccf80fb/ghc >--------------------------------------------------------------- commit a887c5c8240fcdb3f0b1b9bd6c892787dccf80fb Author: Ben Gamari Date: Mon Jun 12 13:34:52 2017 -0400 Archive source distribution >--------------------------------------------------------------- a887c5c8240fcdb3f0b1b9bd6c892787dccf80fb 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 Sat Jun 17 13:53:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:53:02 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: bindist: Compress with threaded xz by default (70e1e11) Message-ID: <20170617135302.E89223A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/70e1e11b3dd2677bb758011da3cc0bcb9f87f3ad/ghc >--------------------------------------------------------------- commit 70e1e11b3dd2677bb758011da3cc0bcb9f87f3ad Author: Ben Gamari Date: Sun Jun 4 12:19:13 2017 -0400 bindist: Compress with threaded xz by default >--------------------------------------------------------------- 70e1e11b3dd2677bb758011da3cc0bcb9f87f3ad 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 189439e..044c928 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -794,7 +794,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 Sat Jun 17 13:53:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:53:05 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix windows paths (92d7640) Message-ID: <20170617135305.A1EF33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/92d7640c8d95081b17c2784c6d175469f8772081/ghc >--------------------------------------------------------------- commit 92d7640c8d95081b17c2784c6d175469f8772081 Author: Ben Gamari Date: Fri Jun 9 13:50:09 2017 -0400 Fix windows paths >--------------------------------------------------------------- 92d7640c8d95081b17c2784c6d175469f8772081 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 Sat Jun 17 13:53:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:53:08 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Trim whitespace from git output (90fcb1e) Message-ID: <20170617135308.6298C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/90fcb1e8f1fd0664b62b915b4fa5a1b3112882ee/ghc >--------------------------------------------------------------- commit 90fcb1e8f1fd0664b62b915b4fa5a1b3112882ee Author: Ben Gamari Date: Sun Jun 4 11:00:28 2017 -0400 Trim whitespace from git output >--------------------------------------------------------------- 90fcb1e8f1fd0664b62b915b4fa5a1b3112882ee 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 Sat Jun 17 13:53:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 13:53:11 +0000 (UTC) Subject: [commit: ghc] wip/jenkins's head updated: debugging (6aa4332) Message-ID: <20170617135311.757873A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/jenkins' 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. 7208e5e Testing simpler Jenkinsfile 8d0dbf7 Testing 376307d Add THREADS parameter 4b9e062 Refactoring 3519604 Move to scripted pipeline a67c52a Add nofib, bindist, and aarch64 support 70c98a6 Run jobs in parallel 66fe057 Debug 7daefcf Cross d5e2a48 Checkout e29b4ff More things da11119 Kill debugging f7fa958 Unregisterised 97e88fa windows 002ba52 Refactoring, add Windows, fix cross ad6bb58 Debug 518bb35 Reformat e4dd926 Debug 01dd168 Nailed the Windows issue 54c2269 Rework handling of Windows 5181ed1 Fix FreeBSD architecture adee5ed Parametrize on make command d6e5547 Use archiveArtifacts instead of archive 6b555e0 Debug 518a45e Don't run nofib on Windows 9e7a054 Fix Windows PATHs 7601ad8 Disable large address space on FreeBSD 846f1c9 Try again 9a5b253 Hmm d5ef4ed Disable non-Windows builds 61fa6ff Hopefully fix Windows 44bc035 Reenable everything else 0b0f156 Fix configure arguments 85895bc Clean 7fc463a Clean up treatment of tests d0a53b6 Handle documentation cdd2988 Fix tarball generation 7f7897d Fix documentation c6e8ea1 Fix testsuite 27130fb Fix test 94e6a82 Be more explicit e8318c4 Fix JSON serialization 3661177 Fix missing binding a6f6544 Debug 50d7176 More debugging 0b5a27c Fix tarName 0aaf511 Actually call closure 8ed117a Build from source distribution 2824fcf Introduce echo! make target 2102abe Fix tarball names 857fa03 No need to configure ba840ee A bit more paranoia around directory deletion 82839e9 No need to boot 90fcb1e Trim whitespace from git output 3a2dd88 Fix source directory name bb43c66 Debuggging e8ffc6d Debug aefb586 Try adding type annotation 9b034ea Debug b304042 Rip out debug output 70e1e11 bindist: Compress with threaded xz by default ffecf49 Configure bindist 8dda9de Run stage1 tests as well 6fb1f3b Pass BINDIST to make test 99d5b24 Use named argument list 0f274af Rework handling of nofib c6d0f870 Don't try to record commit of bindist 92d7640 Fix windows paths a887c5c Archive source distribution 6bb51f8 Ensure that carch, prefix, and ghcPath are in scope d1a5dcd Fix quoting of carch 964bce4 Fix binding name 5798eb1 Fix GHC path 57ca8ee Show location of stage0 compiler 11cf82f Kill debug output 6aa4332 debugging From git at git.haskell.org Sat Jun 17 20:55:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 20:55:35 +0000 (UTC) Subject: [commit: packages/xhtml] tag '3000.2.2' created Message-ID: <20170617205535.9D42E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/xhtml New tag : 3000.2.2 Referencing: 6953e28e87c2953ec89f821cfb31dc66cfc074eb From git at git.haskell.org Sat Jun 17 20:55:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 20:55:39 +0000 (UTC) Subject: [commit: packages/xhtml] master: Merge pull request #9 from erikd/master (5d7011c) Message-ID: <20170617205539.A7FD03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/xhtml On branch : master Link : http://git.haskell.org/packages/xhtml.git/commitdiff/5d7011c1b728b4b3dbecbf50c2dcf251a04d4653 >--------------------------------------------------------------- commit 5d7011c1b728b4b3dbecbf50c2dcf251a04d4653 Merge: fb9e0bb e4206c4 Author: Erik de Castro Lopo Date: Sun Oct 23 14:23:14 2016 +1100 Merge pull request #9 from erikd/master Fix compiler warnings >--------------------------------------------------------------- 5d7011c1b728b4b3dbecbf50c2dcf251a04d4653 Text/XHtml/Internals.hs | 34 ++++++++++++++++++---------------- 1 file changed, 18 insertions(+), 16 deletions(-) From git at git.haskell.org Sat Jun 17 20:55:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 20:55:41 +0000 (UTC) Subject: [commit: packages/xhtml] master: xhtml.cabal: Add -fwarn-tabs to ghc-options (c92ee47) Message-ID: <20170617205541.ACBAE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/xhtml On branch : master Link : http://git.haskell.org/packages/xhtml.git/commitdiff/c92ee47a1b560e57753e49887e9c8752c33dd8db >--------------------------------------------------------------- commit c92ee47a1b560e57753e49887e9c8752c33dd8db Author: Erik de Castro Lopo Date: Sun Oct 23 15:46:43 2016 +1100 xhtml.cabal: Add -fwarn-tabs to ghc-options >--------------------------------------------------------------- c92ee47a1b560e57753e49887e9c8752c33dd8db xhtml.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/xhtml.cabal b/xhtml.cabal index f31003e..42eb16f 100644 --- a/xhtml.cabal +++ b/xhtml.cabal @@ -40,5 +40,5 @@ library Text.XHtml.Extras, Text.XHtml.Internals - ghc-options: -Wall + ghc-options: -Wall -fwarn-tabs Extensions: CPP From git at git.haskell.org Sat Jun 17 20:55:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 20:55:43 +0000 (UTC) Subject: [commit: packages/xhtml] master: Add .travis.yml file (2793377) Message-ID: <20170617205543.B1FF23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/xhtml On branch : master Link : http://git.haskell.org/packages/xhtml.git/commitdiff/2793377e705e031b48a8517f48613b336d38af91 >--------------------------------------------------------------- commit 2793377e705e031b48a8517f48613b336d38af91 Author: Erik de Castro Lopo Date: Sun Oct 23 14:30:28 2016 +1100 Add .travis.yml file >--------------------------------------------------------------- 2793377e705e031b48a8517f48613b336d38af91 .travis.yml | 26 ++++++++++++++++++++++++++ 1 file changed, 26 insertions(+) diff --git a/.travis.yml b/.travis.yml new file mode 100644 index 0000000..21fa639 --- /dev/null +++ b/.travis.yml @@ -0,0 +1,26 @@ +# language: haskell + +# See http://www.reddit.com/r/haskell/comments/1os3f6/how_to_use_travisci_with_multiple_ghc_versions/ + +env: + - GHCVER=7.6.3 + - GHCVER=7.8.4 + - GHCVER=7.10.3 + - GHCVER=8.0.1 + +before_install: + - sudo add-apt-repository -y ppa:hvr/ghc + - sudo apt-get update + - sudo apt-get install cabal-install-1.24 ghc-$GHCVER + - export PATH=/opt/ghc/$GHCVER/bin:$PATH + +install: + - cabal-1.24 update + - cabal-1.24 install --only-dependencies --enable-tests + +script: + - cabal-1.24 configure --enable-tests + - cabal-1.24 build + - cabal-1.24 check + - cabal-1.24 haddock + - cabal-1.24 sdist From git at git.haskell.org Sat Jun 17 20:55:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 20:55:37 +0000 (UTC) Subject: [commit: packages/xhtml] master: Fix compiler warnings (e4206c4) Message-ID: <20170617205537.A2BA83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/xhtml On branch : master Link : http://git.haskell.org/packages/xhtml.git/commitdiff/e4206c4879a590c688fab6a5272aac5d48a45b8b >--------------------------------------------------------------- commit e4206c4879a590c688fab6a5272aac5d48a45b8b Author: Erik de Castro Lopo Date: Sat Jul 30 18:24:24 2016 +1000 Fix compiler warnings Tested with ghc 7.8.4, 7.10.3 and 8.0.1. >--------------------------------------------------------------- e4206c4879a590c688fab6a5272aac5d48a45b8b Text/XHtml/Internals.hs | 34 ++++++++++++++++++---------------- 1 file changed, 18 insertions(+), 16 deletions(-) diff --git a/Text/XHtml/Internals.hs b/Text/XHtml/Internals.hs index 083f19a..86f031e 100644 --- a/Text/XHtml/Internals.hs +++ b/Text/XHtml/Internals.hs @@ -20,7 +20,9 @@ module Text.XHtml.Internals where import Data.Char +#if __GLASGOW_HASKELL__ <= 708 import Data.Monoid +#endif infixr 2 +++ -- combining Html infixr 7 << -- nesting Html @@ -318,10 +320,10 @@ prettyHtml' (HtmlTag -- | Show a start tag renderTag :: Bool -- ^ 'True' if the empty tag shorthand should be used - -> String -- ^ Tag name - -> [HtmlAttr] -- ^ Attributes - -> String -- ^ Whitespace to add after attributes - -> ShowS + -> String -- ^ Tag name + -> [HtmlAttr] -- ^ Attributes + -> String -- ^ Whitespace to add after attributes + -> ShowS renderTag empty name attrs nl r = "<" ++ name ++ shownAttrs ++ nl ++ close ++ r where @@ -335,8 +337,8 @@ renderTag empty name attrs nl r -- | Show an end tag renderEndTag :: String -- ^ Tag name - -> String -- ^ Whitespace to add after tag name - -> ShowS + -> String -- ^ Whitespace to add after tag name + -> ShowS renderEndTag name nl r = "" ++ r @@ -344,17 +346,17 @@ renderEndTag name nl r = "" ++ r -- short-hand. validHtmlITags :: [String] validHtmlITags = [ - "area", - "base", - "basefont", - "br", + "area", + "base", + "basefont", + "br", "col", "frame", - "hr", - "img", - "input", + "hr", + "img", + "input", "isindex", "link", - "meta", - "param" - ] + "meta", + "param" + ] From git at git.haskell.org Sat Jun 17 20:55:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 20:55:45 +0000 (UTC) Subject: [commit: packages/xhtml] master: Convert README to markdown (6102d2c) Message-ID: <20170617205545.B75EA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/xhtml On branch : master Link : http://git.haskell.org/packages/xhtml.git/commitdiff/6102d2c12977802193b6271b91a00d833e6f7d0e >--------------------------------------------------------------- commit 6102d2c12977802193b6271b91a00d833e6f7d0e Author: Erik de Castro Lopo Date: Sun Oct 23 14:36:21 2016 +1100 Convert README to markdown And add a travis build status badge. >--------------------------------------------------------------- 6102d2c12977802193b6271b91a00d833e6f7d0e README | 2 -- README.md | 7 +++++++ 2 files changed, 7 insertions(+), 2 deletions(-) diff --git a/README b/README deleted file mode 100644 index 9f28597..0000000 --- a/README +++ /dev/null @@ -1,2 +0,0 @@ -This package provides combinators for producing XHTML 1.0, including -the Strict, Transitional and Frameset variants. diff --git a/README.md b/README.md new file mode 100644 index 0000000..cb3b757 --- /dev/null +++ b/README.md @@ -0,0 +1,7 @@ +XHTML +----- + +[![Build Status](https://secure.travis-ci.org/haskell/xhtml.svg?branch=master)](http://travis-ci.org/haskell/xhtml) + +This package provides combinators for producing XHTML 1.0, including +the Strict, Transitional and Frameset variants. From git at git.haskell.org Sat Jun 17 20:55:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 20:55:47 +0000 (UTC) Subject: [commit: packages/xhtml] master: Merge pull request #10 from erikd/master (45e5cb8) Message-ID: <20170617205547.BCE4E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/xhtml On branch : master Link : http://git.haskell.org/packages/xhtml.git/commitdiff/45e5cb820a129780407bc37968364e4f64174f7d >--------------------------------------------------------------- commit 45e5cb820a129780407bc37968364e4f64174f7d Merge: 5d7011c c92ee47 Author: Erik de Castro Lopo Date: Sun Oct 23 15:54:20 2016 +1100 Merge pull request #10 from erikd/master Add .travis.yml and convert README to markdown >--------------------------------------------------------------- 45e5cb820a129780407bc37968364e4f64174f7d .travis.yml | 26 ++++++++++++++++++++++++++ README | 2 -- README.md | 7 +++++++ xhtml.cabal | 2 +- 4 files changed, 34 insertions(+), 3 deletions(-) From git at git.haskell.org Sat Jun 17 20:55:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 20:55:49 +0000 (UTC) Subject: [commit: packages/xhtml] master: Add GHC 8.2.1 to test-matrix (bcd513f) Message-ID: <20170617205549.C1FDB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/xhtml On branch : master Link : http://git.haskell.org/packages/xhtml.git/commitdiff/bcd513feda497fa2f0196101aa55f9d488d58ef5 >--------------------------------------------------------------- commit bcd513feda497fa2f0196101aa55f9d488d58ef5 Author: Herbert Valerio Riedel Date: Tue Apr 18 10:47:21 2017 +0200 Add GHC 8.2.1 to test-matrix >--------------------------------------------------------------- bcd513feda497fa2f0196101aa55f9d488d58ef5 .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index 21fa639..8f93745 100644 --- a/.travis.yml +++ b/.travis.yml @@ -7,6 +7,7 @@ env: - GHCVER=7.8.4 - GHCVER=7.10.3 - GHCVER=8.0.1 + - GHCVER=8.2.1 before_install: - sudo add-apt-repository -y ppa:hvr/ghc From git at git.haskell.org Sat Jun 17 20:55:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 20:55:51 +0000 (UTC) Subject: [commit: packages/xhtml] master: Wiggle Travis script, again (74c02d5) Message-ID: <20170617205551.C731E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/xhtml On branch : master Link : http://git.haskell.org/packages/xhtml.git/commitdiff/74c02d5bbd3985b87d294b3bc82d63984d5db444 >--------------------------------------------------------------- commit 74c02d5bbd3985b87d294b3bc82d63984d5db444 Author: Herbert Valerio Riedel Date: Tue Apr 18 11:04:43 2017 +0200 Wiggle Travis script, again >--------------------------------------------------------------- 74c02d5bbd3985b87d294b3bc82d63984d5db444 .travis.yml | 28 +++++++++++++++++----------- 1 file changed, 17 insertions(+), 11 deletions(-) diff --git a/.travis.yml b/.travis.yml index 8f93745..c1611f5 100644 --- a/.travis.yml +++ b/.travis.yml @@ -2,26 +2,32 @@ # See http://www.reddit.com/r/haskell/comments/1os3f6/how_to_use_travisci_with_multiple_ghc_versions/ +dist: trusty +sudo: required + env: + - GHCVER=7.0.4 + - GHCVER=7.2.2 + - GHCVER=7.4.2 - GHCVER=7.6.3 - GHCVER=7.8.4 - GHCVER=7.10.3 - - GHCVER=8.0.1 + - GHCVER=8.0.2 - GHCVER=8.2.1 before_install: - sudo add-apt-repository -y ppa:hvr/ghc - - sudo apt-get update - - sudo apt-get install cabal-install-1.24 ghc-$GHCVER - - export PATH=/opt/ghc/$GHCVER/bin:$PATH + - travis_retry sudo apt-get update + - travis_retry sudo apt-get install cabal-install-2.0 ghc-$GHCVER + - export PATH=/opt/ghc/bin:$PATH install: - - cabal-1.24 update - - cabal-1.24 install --only-dependencies --enable-tests + - travis_retry cabal update + - cabal install --only-dependencies --enable-tests script: - - cabal-1.24 configure --enable-tests - - cabal-1.24 build - - cabal-1.24 check - - cabal-1.24 haddock - - cabal-1.24 sdist + - cabal configure --enable-tests + - cabal build + - cabal check + - cabal haddock + - cabal sdist From git at git.haskell.org Sat Jun 17 20:55:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 20:55:53 +0000 (UTC) Subject: [commit: packages/xhtml] master: Update .cabal file & reduce CPP-processing to the bare minimum (eb81b30) Message-ID: <20170617205553.CCA293A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/xhtml On branch : master Link : http://git.haskell.org/packages/xhtml.git/commitdiff/eb81b3090ab78cd3a57507456d0401509204bc48 >--------------------------------------------------------------- commit eb81b3090ab78cd3a57507456d0401509204bc48 Author: Herbert Valerio Riedel Date: Tue Apr 18 11:25:42 2017 +0200 Update .cabal file & reduce CPP-processing to the bare minimum >--------------------------------------------------------------- eb81b3090ab78cd3a57507456d0401509204bc48 Text/XHtml.hs | 4 ---- Text/XHtml/BlockTable.hs | 4 ---- Text/XHtml/Debug.hs | 4 ---- Text/XHtml/Extras.hs | 4 ---- Text/XHtml/Frameset.hs | 4 ---- Text/XHtml/Frameset/Attributes.hs | 4 ---- Text/XHtml/Frameset/Elements.hs | 4 ---- Text/XHtml/Internals.hs | 5 +---- Text/XHtml/Strict.hs | 4 ---- Text/XHtml/Strict/Attributes.hs | 4 ---- Text/XHtml/Strict/Elements.hs | 4 ---- Text/XHtml/Table.hs | 5 ----- Text/XHtml/Transitional.hs | 4 ---- Text/XHtml/Transitional/Attributes.hs | 4 ---- Text/XHtml/Transitional/Elements.hs | 4 ---- xhtml.cabal | 12 +++++++++--- 16 files changed, 10 insertions(+), 64 deletions(-) diff --git a/Text/XHtml.hs b/Text/XHtml.hs index 99b1cd2..8c89d8c 100644 --- a/Text/XHtml.hs +++ b/Text/XHtml.hs @@ -1,7 +1,3 @@ -#if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Safe #-} -#endif - ----------------------------------------------------------------------------- -- | -- Module : Text.XHtml diff --git a/Text/XHtml/BlockTable.hs b/Text/XHtml/BlockTable.hs index 42718a8..499dd62 100644 --- a/Text/XHtml/BlockTable.hs +++ b/Text/XHtml/BlockTable.hs @@ -1,7 +1,3 @@ -#if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Safe #-} -#endif - ----------------------------------------------------------------------------- -- | -- Module : Text.XHtml.BlockTable diff --git a/Text/XHtml/Debug.hs b/Text/XHtml/Debug.hs index aa07dd0..fc71d7a 100644 --- a/Text/XHtml/Debug.hs +++ b/Text/XHtml/Debug.hs @@ -1,8 +1,4 @@ {-# OPTIONS_HADDOCK hide #-} --- #hide -#if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Safe #-} -#endif -- | This module contains functions for displaying -- HTML as a pretty tree. diff --git a/Text/XHtml/Extras.hs b/Text/XHtml/Extras.hs index 835ca37..5208625 100644 --- a/Text/XHtml/Extras.hs +++ b/Text/XHtml/Extras.hs @@ -1,7 +1,3 @@ -#if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Safe #-} -#endif - module Text.XHtml.Extras where import Text.XHtml.Internals diff --git a/Text/XHtml/Frameset.hs b/Text/XHtml/Frameset.hs index 453bff1..becfb39 100644 --- a/Text/XHtml/Frameset.hs +++ b/Text/XHtml/Frameset.hs @@ -1,7 +1,3 @@ -#if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Safe #-} -#endif - -- | Produces XHTML 1.0 Frameset. module Text.XHtml.Frameset ( -- * Data types diff --git a/Text/XHtml/Frameset/Attributes.hs b/Text/XHtml/Frameset/Attributes.hs index 8465965..7aec0dd 100644 --- a/Text/XHtml/Frameset/Attributes.hs +++ b/Text/XHtml/Frameset/Attributes.hs @@ -1,8 +1,4 @@ {-# OPTIONS_HADDOCK hide #-} --- #hide -#if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Safe #-} -#endif module Text.XHtml.Frameset.Attributes where diff --git a/Text/XHtml/Frameset/Elements.hs b/Text/XHtml/Frameset/Elements.hs index f6de454..f925784 100644 --- a/Text/XHtml/Frameset/Elements.hs +++ b/Text/XHtml/Frameset/Elements.hs @@ -1,8 +1,4 @@ {-# OPTIONS_HADDOCK hide #-} --- #hide -#if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Safe #-} -#endif module Text.XHtml.Frameset.Elements where diff --git a/Text/XHtml/Internals.hs b/Text/XHtml/Internals.hs index 86f031e..7d5ac22 100644 --- a/Text/XHtml/Internals.hs +++ b/Text/XHtml/Internals.hs @@ -1,8 +1,5 @@ +{-# LANGUAGE CPP #-} {-# OPTIONS_HADDOCK hide #-} --- #hide -#if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Safe #-} -#endif ----------------------------------------------------------------------------- -- | diff --git a/Text/XHtml/Strict.hs b/Text/XHtml/Strict.hs index 73dd343..c51f9bf 100644 --- a/Text/XHtml/Strict.hs +++ b/Text/XHtml/Strict.hs @@ -1,7 +1,3 @@ -#if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Safe #-} -#endif - -- | Produces XHTML 1.0 Strict. module Text.XHtml.Strict ( -- * Data types diff --git a/Text/XHtml/Strict/Attributes.hs b/Text/XHtml/Strict/Attributes.hs index 1fdc2de..468eb1a 100644 --- a/Text/XHtml/Strict/Attributes.hs +++ b/Text/XHtml/Strict/Attributes.hs @@ -1,8 +1,4 @@ {-# OPTIONS_HADDOCK hide #-} --- #hide -#if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Safe #-} -#endif module Text.XHtml.Strict.Attributes where diff --git a/Text/XHtml/Strict/Elements.hs b/Text/XHtml/Strict/Elements.hs index 367631e..25b94d4 100644 --- a/Text/XHtml/Strict/Elements.hs +++ b/Text/XHtml/Strict/Elements.hs @@ -1,8 +1,4 @@ {-# OPTIONS_HADDOCK hide #-} --- #hide -#if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Safe #-} -#endif module Text.XHtml.Strict.Elements where diff --git a/Text/XHtml/Table.hs b/Text/XHtml/Table.hs index b94b4db..c243673 100644 --- a/Text/XHtml/Table.hs +++ b/Text/XHtml/Table.hs @@ -1,8 +1,3 @@ -{-# LANGUAGE CPP #-} -#if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Safe #-} -#endif - -- | Table combinators for XHTML. module Text.XHtml.Table (HtmlTable, HTMLTABLE(..), (), above, (<->), beside, diff --git a/Text/XHtml/Transitional.hs b/Text/XHtml/Transitional.hs index 99af40c..97f6430 100644 --- a/Text/XHtml/Transitional.hs +++ b/Text/XHtml/Transitional.hs @@ -1,7 +1,3 @@ -#if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Safe #-} -#endif - -- | Produces XHTML 1.0 Transitional. module Text.XHtml.Transitional ( -- * Data types diff --git a/Text/XHtml/Transitional/Attributes.hs b/Text/XHtml/Transitional/Attributes.hs index fb78c63..95b2e8e 100644 --- a/Text/XHtml/Transitional/Attributes.hs +++ b/Text/XHtml/Transitional/Attributes.hs @@ -1,8 +1,4 @@ {-# OPTIONS_HADDOCK hide #-} --- #hide -#if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Safe #-} -#endif module Text.XHtml.Transitional.Attributes where diff --git a/Text/XHtml/Transitional/Elements.hs b/Text/XHtml/Transitional/Elements.hs index 7711b17..47303e3 100644 --- a/Text/XHtml/Transitional/Elements.hs +++ b/Text/XHtml/Transitional/Elements.hs @@ -1,8 +1,4 @@ {-# OPTIONS_HADDOCK hide #-} --- #hide -#if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Safe #-} -#endif module Text.XHtml.Transitional.Elements where diff --git a/xhtml.cabal b/xhtml.cabal index 42eb16f..6b7676e 100644 --- a/xhtml.cabal +++ b/xhtml.cabal @@ -13,15 +13,22 @@ Description: This package provides combinators for producing Stability: Stable Category: Web, XML, Pretty Printer Homepage: https://github.com/haskell/xhtml +Bug-Reports: https://github.com/haskell/xhtml/issues Build-type: Simple -Cabal-version: >= 1.6 +Cabal-version: >= 1.10 Source-repository head type: git location: https://github.com/haskell/xhtml library - Build-depends: base >= 4.0 && < 5.0 + Default-Language: Haskell2010 + Other-Extensions: CPP + if impl(ghc >= 7.2) + Default-Extensions: Safe + + Build-depends: base >= 4 && < 5 + Exposed-modules: Text.XHtml, Text.XHtml.Frameset, @@ -41,4 +48,3 @@ library Text.XHtml.Internals ghc-options: -Wall -fwarn-tabs - Extensions: CPP From git at git.haskell.org Sat Jun 17 20:55:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 20:55:55 +0000 (UTC) Subject: [commit: packages/xhtml] master: Make xhtml -Wcompat clean by adding semigroup instances (8a8c8a4) Message-ID: <20170617205555.D212F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/xhtml On branch : master Link : http://git.haskell.org/packages/xhtml.git/commitdiff/8a8c8a48bac2d3ed306b610a2e9fa393b5a7ffa5 >--------------------------------------------------------------- commit 8a8c8a48bac2d3ed306b610a2e9fa393b5a7ffa5 Author: Herbert Valerio Riedel Date: Tue Apr 18 12:05:38 2017 +0200 Make xhtml -Wcompat clean by adding semigroup instances This also bumps xhtml's version to 3000.2.2, since the new instance represents a user-visible API addition. >--------------------------------------------------------------- 8a8c8a48bac2d3ed306b610a2e9fa393b5a7ffa5 Text/XHtml/Internals.hs | 13 +++++++------ xhtml.cabal | 17 ++++++++++++++--- 2 files changed, 21 insertions(+), 9 deletions(-) diff --git a/Text/XHtml/Internals.hs b/Text/XHtml/Internals.hs index 7d5ac22..7de94d5 100644 --- a/Text/XHtml/Internals.hs +++ b/Text/XHtml/Internals.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} {-# OPTIONS_HADDOCK hide #-} ----------------------------------------------------------------------------- @@ -17,9 +16,7 @@ module Text.XHtml.Internals where import Data.Char -#if __GLASGOW_HASKELL__ <= 708 -import Data.Monoid -#endif +import qualified Data.Semigroup as Sem infixr 2 +++ -- combining Html infixr 7 << -- nesting Html @@ -66,9 +63,13 @@ instance Show HtmlAttr where showString "=" . shows val -instance Monoid Html where +-- | @since 3000.2.2 +instance Sem.Semigroup Html where + (<>) = (+++) + +instance Sem.Monoid Html where mempty = noHtml - mappend = (+++) + mappend = (Sem.<>) -- | HTML is the class of things that can be validly put -- inside an HTML tag. So this can be one or more 'Html' elements, diff --git a/xhtml.cabal b/xhtml.cabal index 6b7676e..104bc64 100644 --- a/xhtml.cabal +++ b/xhtml.cabal @@ -1,5 +1,5 @@ Name: xhtml -Version: 3000.2.1 +Version: 3000.2.2 Copyright: Bjorn Bringert 2004-2006, Andy Gill and the Oregon Graduate Institute of Science and Technology, 1999-2001 Maintainer: Chris Dornan @@ -23,11 +23,22 @@ Source-repository head library Default-Language: Haskell2010 - Other-Extensions: CPP if impl(ghc >= 7.2) Default-Extensions: Safe - Build-depends: base >= 4 && < 5 + Build-depends: base >= 4 && < 5 + if impl(ghc >= 8.0) + -- Enable warnings about potential future incompatibilities + ghc-options: -Wcompat -Wnoncanonical-monadfail-instances -Wnoncanonical-monad-instances + else + -- This provides compatibility with versions prior to GHC 8.0 / base-4.9, when `Data.Semigroup` + -- still lived in `semigroups`. + + -- Note: semigroups-0.8 is a reasonably early version depending only on base & containers, + -- and `xhtml` only needs to define the class instance + -- so we can easily support a wide range of major + -- versions of `semigroups` + Build-depends: semigroups >= 0.8 && < 0.19 Exposed-modules: Text.XHtml, From git at git.haskell.org Sat Jun 17 20:55:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Jun 2017 20:55:57 +0000 (UTC) Subject: [commit: packages/xhtml] master: Finalize for 3000.2.2 release (6358594) Message-ID: <20170617205557.D6A5C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/xhtml On branch : master Link : http://git.haskell.org/packages/xhtml.git/commitdiff/6358594eb5139f6760e2ada72718d69fed5a1015 >--------------------------------------------------------------- commit 6358594eb5139f6760e2ada72718d69fed5a1015 Author: Herbert Valerio Riedel Date: Sat Jun 17 22:53:25 2017 +0200 Finalize for 3000.2.2 release >--------------------------------------------------------------- 6358594eb5139f6760e2ada72718d69fed5a1015 .gitignore | 4 +++- ChangeLog.md | 5 +++++ xhtml.cabal | 1 + 3 files changed, 9 insertions(+), 1 deletion(-) diff --git a/.gitignore b/.gitignore index 468db0f..c487581 100644 --- a/.gitignore +++ b/.gitignore @@ -1,7 +1,9 @@ .project -dist +dist/ +dist-newstyle/ GNUmakefile dist-install/ ghc.mk test.hs .hub +.ghc.environment.* diff --git a/ChangeLog.md b/ChangeLog.md new file mode 100644 index 0000000..2030f31 --- /dev/null +++ b/ChangeLog.md @@ -0,0 +1,5 @@ +## 3000.2.2 + +- Add `Semigroup Html` instance +- Update to `cabal-version:>=1.10` +- Clean-up compiler warnings diff --git a/xhtml.cabal b/xhtml.cabal index 104bc64..fba4bbc 100644 --- a/xhtml.cabal +++ b/xhtml.cabal @@ -16,6 +16,7 @@ Homepage: https://github.com/haskell/xhtml Bug-Reports: https://github.com/haskell/xhtml/issues Build-type: Simple Cabal-version: >= 1.10 +extra-source-files: ChangeLog.md Source-repository head type: git From git at git.haskell.org Sun Jun 18 02:53:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Jun 2017 02:53:49 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Handle testsuite on Windows (046aafc99) Message-ID: <20170618025349.A74ED3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/046aafc9961e5f59de057c89925f0f7bcd614a82/ghc >--------------------------------------------------------------- commit 046aafc9961e5f59de057c89925f0f7bcd614a82 Author: Ben Gamari Date: Sat Jun 17 22:53:30 2017 -0400 Handle testsuite on Windows >--------------------------------------------------------------- 046aafc9961e5f59de057c89925f0f7bcd614a82 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 Sun Jun 18 03:34:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Jun 2017 03:34:31 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: debug win32 (74d42f6) Message-ID: <20170618033431.518CE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/74d42f6772f2f7e92f5527df28dd1936157f5fdf/ghc >--------------------------------------------------------------- commit 74d42f6772f2f7e92f5527df28dd1936157f5fdf Author: Ben Gamari Date: Sat Jun 17 23:34:18 2017 -0400 debug win32 >--------------------------------------------------------------- 74d42f6772f2f7e92f5527df28dd1936157f5fdf 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 Sun Jun 18 13:35:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Jun 2017 13:35:54 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Ugh, sh not echo (ba04a99) Message-ID: <20170618133554.D38AE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/ba04a99a49d094d030e74a00cf9fcd23e9cd5ce7/ghc >--------------------------------------------------------------- commit ba04a99a49d094d030e74a00cf9fcd23e9cd5ce7 Author: Ben Gamari Date: Sun Jun 18 09:35:42 2017 -0400 Ugh, sh not echo >--------------------------------------------------------------- ba04a99a49d094d030e74a00cf9fcd23e9cd5ce7 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 Sun Jun 18 16:02:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Jun 2017 16:02:00 +0000 (UTC) Subject: [commit: ghc] master: Fix out-of-date comments in TyCoRep (559a0c5) Message-ID: <20170618160200.13FD33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/559a0c5d5458401f54f3680f32675a958ccb0d2b/ghc >--------------------------------------------------------------- commit 559a0c5d5458401f54f3680f32675a958ccb0d2b Author: Ryan Scott Date: Sun Jun 18 12:00:06 2017 -0400 Fix out-of-date comments in TyCoRep s/tyVarsOfType/tyCoFVsOfType/g >--------------------------------------------------------------- 559a0c5d5458401f54f3680f32675a958ccb0d2b compiler/types/TyCoRep.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index e6afece..fbf0a9f 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -1352,21 +1352,21 @@ tyCoVarsOfType :: Type -> TyCoVarSet -- See Note [Free variables of types] tyCoVarsOfType ty = fvVarSet $ tyCoFVsOfType ty --- | `tyVarsOfType` that returns free variables of a type in a deterministic +-- | `tyCoFVsOfType` that returns free variables of a type in a deterministic -- set. For explanation of why using `VarSet` is not deterministic see -- Note [Deterministic FV] in FV. tyCoVarsOfTypeDSet :: Type -> DTyCoVarSet -- See Note [Free variables of types] tyCoVarsOfTypeDSet ty = fvDVarSet $ tyCoFVsOfType ty --- | `tyVarsOfType` that returns free variables of a type in deterministic +-- | `tyCoFVsOfType` that returns free variables of a type in deterministic -- order. For explanation of why using `VarSet` is not deterministic see -- Note [Deterministic FV] in FV. tyCoVarsOfTypeList :: Type -> [TyCoVar] -- See Note [Free variables of types] tyCoVarsOfTypeList ty = fvVarList $ tyCoFVsOfType ty --- | The worker for `tyVarsOfType` and `tyVarsOfTypeList`. +-- | The worker for `tyCoFVsOfType` and `tyCoFVsOfTypeList`. -- The previous implementation used `unionVarSet` which is O(n+m) and can -- make the function quadratic. -- It's exported, so that it can be composed with From git at git.haskell.org Sun Jun 18 18:31:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Jun 2017 18:31:59 +0000 (UTC) Subject: [commit: ghc] master: Typofix in Data.Type.Equality comments (df32880) Message-ID: <20170618183159.271973A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/df3288000e860856f0fe0ffe67669da9ae5a0a03/ghc >--------------------------------------------------------------- commit df3288000e860856f0fe0ffe67669da9ae5a0a03 Author: Ryan Scott Date: Sun Jun 18 14:30:38 2017 -0400 Typofix in Data.Type.Equality comments >--------------------------------------------------------------- df3288000e860856f0fe0ffe67669da9ae5a0a03 libraries/base/Data/Type/Equality.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/Data/Type/Equality.hs b/libraries/base/Data/Type/Equality.hs index 69da70b..173e3c4 100644 --- a/libraries/base/Data/Type/Equality.hs +++ b/libraries/base/Data/Type/Equality.hs @@ -112,7 +112,7 @@ gcastWith Refl x = x apply :: (f :~: g) -> (a :~: b) -> (f a :~: g b) apply Refl Refl = Refl --- | Extract equality of the arguments from an equality of a applied types +-- | Extract equality of the arguments from an equality of applied types inner :: (f a :~: g b) -> (a :~: b) inner Refl = Refl From git at git.haskell.org Sun Jun 18 18:31:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Jun 2017 18:31:56 +0000 (UTC) Subject: [commit: ghc] master: Look through type synonyms in existential contexts when deriving Functor (8573100) Message-ID: <20170618183156.695A03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/85731000d8b13476ed3c5bde22af610a27fb00f8/ghc >--------------------------------------------------------------- commit 85731000d8b13476ed3c5bde22af610a27fb00f8 Author: Ryan Scott Date: Sun Jun 18 14:23:43 2017 -0400 Look through type synonyms in existential contexts when deriving Functor Summary: This amounts to using `exactTyCoVarsOfType` instead of `tyCoVarsOfType` in the right place. I also fixed a similar issue for `-XDatatypeContexts` while I was in town (but couldn't be bothered to add a test for it). Test Plan: make test TEST=T13813 Reviewers: austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #13813 Differential Revision: https://phabricator.haskell.org/D3635 >--------------------------------------------------------------- 85731000d8b13476ed3c5bde22af610a27fb00f8 compiler/typecheck/TcDerivUtils.hs | 18 ++++++++++++++++-- testsuite/tests/deriving/should_compile/T13813.hs | 13 +++++++++++++ testsuite/tests/deriving/should_compile/all.T | 1 + 3 files changed, 30 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcDerivUtils.hs b/compiler/typecheck/TcDerivUtils.hs index 3a662d9..8991407 100644 --- a/compiler/typecheck/TcDerivUtils.hs +++ b/compiler/typecheck/TcDerivUtils.hs @@ -512,7 +512,8 @@ cond_functorOK allowFunctions allowExQuantifiedLastTyVar _ rep_tc tc_tvs = tyConTyVars rep_tc Just (_, last_tv) = snocView tc_tvs bad_stupid_theta = filter is_bad (tyConStupidTheta rep_tc) - is_bad pred = last_tv `elemVarSet` tyCoVarsOfType pred + is_bad pred = last_tv `elemVarSet` exactTyCoVarsOfType pred + -- See Note [Check that the type variable is truly universal] data_cons = tyConDataCons rep_tc check_con con = allValid (check_universal con : foldDataConArgs (ft_check con) con) @@ -524,7 +525,7 @@ cond_functorOK allowFunctions allowExQuantifiedLastTyVar _ rep_tc -- in TcGenFunctor | Just tv <- getTyVar_maybe (last (tyConAppArgs (dataConOrigResTy con))) , tv `elem` dataConUnivTyVars con - , not (tv `elemVarSet` tyCoVarsOfTypes (dataConTheta con)) + , not (tv `elemVarSet` exactTyCoVarsOfTypes (dataConTheta con)) = IsValid -- See Note [Check that the type variable is truly universal] | otherwise = NotValid (badCon con existential) @@ -666,4 +667,17 @@ As a result, T can have a derived Foldable instance: foldr _ z T6 = z See Note [DeriveFoldable with ExistentialQuantification] in TcGenFunctor. + +For Functor and Traversable, we must take care not to let type synonyms +unfairly reject a type for not being truly universally quantified. An +example of this is: + + type C (a :: Constraint) b = a + data T a b = C (Show a) b => MkT b + +Here, the existential context (C (Show a) b) does technically mention the last +type variable b. But this is OK, because expanding the type synonym C would +give us the context (Show a), which doesn't mention b. Therefore, we must make +sure to expand type synonyms before performing this check. Not doing so led to +Trac #13813. -} diff --git a/testsuite/tests/deriving/should_compile/T13813.hs b/testsuite/tests/deriving/should_compile/T13813.hs new file mode 100644 index 0000000..e63869c --- /dev/null +++ b/testsuite/tests/deriving/should_compile/T13813.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE ConstraintKinds #-} +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE ExistentialQuantification #-} +{-# LANGUAGE KindSignatures #-} +{-# LANGUAGE StandaloneDeriving #-} +module T13813 where + +import GHC.Exts (Constraint) + +type C (a :: Constraint) b = a + +data T a b = C (Show a) b => MkT b +deriving instance Functor (T a) diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T index 36476d5..d1615ab 100644 --- a/testsuite/tests/deriving/should_compile/all.T +++ b/testsuite/tests/deriving/should_compile/all.T @@ -91,3 +91,4 @@ test('T13297', normal, compile, ['']) test('T13758', normal, compile, ['']) test('drv-empty-data', [normalise_errmsg_fun(just_the_deriving)],compile, ['-ddump-deriv -dsuppress-uniques']) test('drv-phantom', [normalise_errmsg_fun(just_the_deriving)],compile, ['-ddump-deriv -dsuppress-uniques']) +test('T13813', normal, compile, ['']) From git at git.haskell.org Sun Jun 18 20:35:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Jun 2017 20:35:33 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Ensure HOME is expanded (557dfd7) Message-ID: <20170618203533.2932B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/557dfd77dc4f98803cd4808e932ba8056fc403f2/ghc >--------------------------------------------------------------- commit 557dfd77dc4f98803cd4808e932ba8056fc403f2 Author: Ben Gamari Date: Sun Jun 18 16:35:12 2017 -0400 Ensure HOME is expanded >--------------------------------------------------------------- 557dfd77dc4f98803cd4808e932ba8056fc403f2 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 Mon Jun 19 11:27:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 11:27:21 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: No trailing newline (068b46e) Message-ID: <20170619112721.7FFCD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/068b46e23f91a1888d0c6313c596f2042d23b723/ghc >--------------------------------------------------------------- commit 068b46e23f91a1888d0c6313c596f2042d23b723 Author: Ben Gamari Date: Mon Jun 19 07:27:07 2017 -0400 No trailing newline >--------------------------------------------------------------- 068b46e23f91a1888d0c6313c596f2042d23b723 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 Mon Jun 19 12:16:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 12:16:04 +0000 (UTC) Subject: [commit: ghc] master: rts: Ensure that new capability count is > 0 (b9f9670) Message-ID: <20170619121604.BE41A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b9f9670c8cf4eac8798a8cb3e683d0411f9e94ec/ghc >--------------------------------------------------------------- commit b9f9670c8cf4eac8798a8cb3e683d0411f9e94ec Author: Ben Gamari Date: Fri Jun 16 15:23:07 2017 -0400 rts: Ensure that new capability count is > 0 The Haskell wrapper already checks this but we should also check it in the RTS to catch non-Haskell callers. See #13832. >--------------------------------------------------------------- b9f9670c8cf4eac8798a8cb3e683d0411f9e94ec rts/Schedule.c | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/rts/Schedule.c b/rts/Schedule.c index b4f60f8..7950785 100644 --- a/rts/Schedule.c +++ b/rts/Schedule.c @@ -2178,7 +2178,13 @@ setNumCapabilities (uint32_t new_n_capabilities USED_IF_THREADS) Capability *old_capabilities = NULL; uint32_t old_n_capabilities = n_capabilities; - if (new_n_capabilities == enabled_capabilities) return; + if (new_n_capabilities == enabled_capabilities) { + return; + } else if (new_n_capabilities <= 0) { + errorBelch("setNumCapabilities: Capability count must be positive"); + return; + } + debugTrace(DEBUG_sched, "changing the number of Capabilities from %d to %d", enabled_capabilities, new_n_capabilities); From git at git.haskell.org Mon Jun 19 12:16:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 12:16:07 +0000 (UTC) Subject: [commit: ghc] master: rts: A bit of cleanup around the eventlog (e12ea39) Message-ID: <20170619121607.7D5F63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e12ea39ee508b83f62f68e1939ce025e1d9ea15a/ghc >--------------------------------------------------------------- commit e12ea39ee508b83f62f68e1939ce025e1d9ea15a Author: Ben Gamari Date: Fri Jun 16 15:41:18 2017 -0400 rts: A bit of cleanup around the eventlog >--------------------------------------------------------------- e12ea39ee508b83f62f68e1939ce025e1d9ea15a rts/eventlog/EventLog.c | 97 +++++++++++++++---------------------------------- 1 file changed, 30 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 e12ea39ee508b83f62f68e1939ce025e1d9ea15a From git at git.haskell.org Mon Jun 19 12:16:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 12:16:10 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add testcase for #13822 (04ca036) Message-ID: <20170619121610.7ED613A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/04ca0360a6b38627c2608ed7468f4d8c46257e3a/ghc >--------------------------------------------------------------- commit 04ca0360a6b38627c2608ed7468f4d8c46257e3a Author: Ben Gamari Date: Sun Jun 18 16:48:31 2017 -0400 testsuite: Add testcase for #13822 Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #13822 Differential Revision: https://phabricator.haskell.org/D3655 >--------------------------------------------------------------- 04ca0360a6b38627c2608ed7468f4d8c46257e3a testsuite/tests/typecheck/should_compile/T13822.hs | 67 ++++++++++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 68 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T13822.hs b/testsuite/tests/typecheck/should_compile/T13822.hs new file mode 100644 index 0000000..5837cc8 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13822.hs @@ -0,0 +1,67 @@ +{-# LANGUAGE GADTs, TypeOperators, PolyKinds, DataKinds, TypeFamilyDependencies, TypeInType, RankNTypes, LambdaCase, EmptyCase #-} + +module T13822 where + +import Data.Kind + +data KIND = STAR | KIND :> KIND + +data Ty :: KIND -> Type where + TInt :: Ty STAR + TBool :: Ty STAR + TMaybe :: Ty (STAR :> STAR) + TApp :: Ty (a :> b) -> (Ty a -> Ty b) + +type family + IK (k :: KIND) = (res :: Type) | res -> k where + IK STAR = Type + IK (a:>b) = IK a -> IK b + +type family + I (t :: Ty k) = (res :: IK k) | res -> t where + I TInt = Int + I TBool = Bool + I TMaybe = Maybe + I (TApp f a) = (I f) (I a) + +data TyRep (k :: KIND) (t :: Ty k) where + TyInt :: TyRep STAR TInt + TyBool :: TyRep STAR TBool + TyMaybe :: TyRep (STAR:>STAR) TMaybe + TyApp :: TyRep (a:>b) f -> TyRep a x -> TyRep b (TApp f x) + +zero :: TyRep STAR a -> I a +zero = \case + TyInt -> 0 + TyBool -> False + TyApp TyMaybe _ -> Nothing + + +-- Inferred type: +-- +-- int :: TyRep STAR TInt -> Int +int rep = zero rep :: Int + +-- bool:: TyRep STAR TBool -> Bool +bool rep = zero rep :: Bool + +-- Previously failed with: +-- +-- v.hs:43:16: error: +-- • Couldn't match kind ‘k’ with ‘'STAR’ +-- ‘k’ is a rigid type variable bound by +-- the inferred type of +-- maybeInt :: (I 'TInt ~ Int, I 'TMaybe ~ Maybe) => +-- TyRep 'STAR ('TApp 'TMaybe 'TInt) -> Maybe Int +-- at v.hs:25:3 +-- When matching the kind of ‘'TMaybe’ +-- Expected type: Maybe Int +-- Actual type: I ('TApp 'TMaybe 'TInt) +-- • In the expression: zero rep :: Maybe Int +-- In an equation for ‘maybeInt’: maybeInt rep = zero rep :: Maybe Int +-- • Relevant bindings include +-- rep :: TyRep 'STAR ('TApp 'TMaybe 'TInt) (bound at v.hs:43:10) +-- maybeInt :: TyRep 'STAR ('TApp 'TMaybe 'TInt) -> Maybe Int +-- (bound at v.hs:43:1) +-- Failed, modules loaded: none. +maybeInt rep = zero rep :: Maybe Int diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index a9eb4ff..b267819 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -563,3 +563,4 @@ test('T13585', [extra_files(['T13585.hs', 'T13585a.hs', 'T13585b.hs'])], run_com test('T13651', normal, compile, ['']) test('T13785', normal, compile, ['']) test('T13804', normal, compile, ['']) +test('T13822', normal, compile, ['']) From git at git.haskell.org Mon Jun 19 12:16:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 12:16:13 +0000 (UTC) Subject: [commit: ghc] master: Add fixity declaration for :~~: (ee9232524) Message-ID: <20170619121613.3D0E13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ee9232524bdba5b268278ec51f30106bb7178ce9/ghc >--------------------------------------------------------------- commit ee9232524bdba5b268278ec51f30106bb7178ce9 Author: Ryan Scott Date: Sun Jun 18 16:49:02 2017 -0400 Add fixity declaration for :~~: We have one for `(:~:)`, but not for `(:~~:)`! Let's fix this oversight. Reviewers: bgamari, austin, hvr Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3657 >--------------------------------------------------------------- ee9232524bdba5b268278ec51f30106bb7178ce9 libraries/base/Data/Type/Equality.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/Data/Type/Equality.hs b/libraries/base/Data/Type/Equality.hs index 173e3c4..8cc34f6 100644 --- a/libraries/base/Data/Type/Equality.hs +++ b/libraries/base/Data/Type/Equality.hs @@ -77,7 +77,7 @@ instance {-# INCOHERENT #-} a ~~ b => a ~ b -- INCOHERENT because we want to use this instance eagerly, even when -- the tyvars are partially unknown. -infix 4 :~: +infix 4 :~:, :~~: -- | Propositional equality. If @a :~: b@ is inhabited by some terminating -- value, then the type @a@ is the same as the type @b at . To use this equality From git at git.haskell.org Mon Jun 19 12:16:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 12:16:16 +0000 (UTC) Subject: [commit: ghc] master: Add T9630 (23f47b1) Message-ID: <20170619121616.9704F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/23f47b15bd45ead7ba50dce276162bb019822e7c/ghc >--------------------------------------------------------------- commit 23f47b15bd45ead7ba50dce276162bb019822e7c Author: David Feuer Date: Sun Jun 18 16:49:14 2017 -0400 Add T9630 This is not the most precise test, unfortunately, but it does demonstrate a modest improvement in compiler residency as a result of the specializer don't-loop patch. A rather less realistic variation on this has somewhat more dramatic effects. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3656 >--------------------------------------------------------------- 23f47b15bd45ead7ba50dce276162bb019822e7c testsuite/tests/perf/compiler/T9630.hs | 21 +++++++ testsuite/tests/perf/compiler/T9630a.hs | 100 ++++++++++++++++++++++++++++++++ testsuite/tests/perf/compiler/all.T | 11 ++++ 3 files changed, 132 insertions(+) diff --git a/testsuite/tests/perf/compiler/T9630.hs b/testsuite/tests/perf/compiler/T9630.hs new file mode 100644 index 0000000..e0bcec2 --- /dev/null +++ b/testsuite/tests/perf/compiler/T9630.hs @@ -0,0 +1,21 @@ +{-# LANGUAGE DeriveGeneric #-} +module T9630 where +import T9630a +import GHC.Generics +import Control.Applicative + +data T = T () () () () + ()()()()()()() + ()()()()()()()()()()()()()()()() + ()()()()()()()()()()()()()()()() + ()()()()()()()()()()()()()()()() + ()()()()()()()()()()()()()()()() + ()()()()()()()()()()()()()()()() + ()()()()()()()()()()()()()()()() + ()()()()()()()()()()()()()()()() + ()()()()()()()()()()()()()()()() + deriving Generic + +instance Serialize T where + get = to <$> gGet + put = gPut . from diff --git a/testsuite/tests/perf/compiler/T9630a.hs b/testsuite/tests/perf/compiler/T9630a.hs new file mode 100644 index 0000000..1d879f2 --- /dev/null +++ b/testsuite/tests/perf/compiler/T9630a.hs @@ -0,0 +1,100 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE RankNTypes #-} + +----------------------------------------------------------------------------- +-- | Modified from cereal, which is +-- Copyright : Lennart Kolmodin, Galois Inc. 2009 +-- License : BSD3-style + +module T9630a ( + Serialize(..), GSerialize (..), Putter, Get + ) where + +import Data.ByteString.Builder (Builder) +import Data.ByteString as B +import GHC.Generics +import Control.Applicative (Applicative (..), (<$>)) + +class Serialize t where + put :: Putter t + get :: Get t + +instance Serialize () where + put () = pure () + get = pure () + +-- Generics + +class GSerialize f where + gPut :: Putter (f a) + gGet :: Get (f a) + +instance (GSerialize a, GSerialize b) => GSerialize (a :*: b) where + gPut (a :*: b) = gPut a *> gPut b + gGet = (:*:) <$> gGet <*> gGet + +instance GSerialize a => GSerialize (M1 i c a) where + gPut = gPut . unM1 + gGet = M1 <$> gGet + +instance Serialize a => GSerialize (K1 i a) where + gPut = put . unK1 + gGet = K1 <$> get + + +-- Put + +data PairS a = PairS a !Builder + +newtype PutM a = Put { unPut :: PairS a } + +type Put = PutM () + +type Putter a = a -> Put + +instance Functor PutM where + fmap f m = Put $ let PairS a w = unPut m in PairS (f a) w + +instance Applicative PutM where + pure a = Put (PairS a mempty) + + m <*> k = Put $ + let PairS f w = unPut m + PairS x w' = unPut k + in PairS (f x) (w `mappend` w') + +-- Get + +data Result r = Fail String B.ByteString + | Partial (B.ByteString -> Result r) + | Done r B.ByteString + + +newtype Get a = Get + { unGet :: forall r. Input -> Buffer -> More + -> Failure r -> Success a r + -> Result r } + +type Input = B.ByteString +type Buffer = Maybe B.ByteString + +type Failure r = Input -> Buffer -> More -> [String] -> String -> Result r +type Success a r = Input -> Buffer -> More -> a -> Result r + +data More + = Complete + | Incomplete (Maybe Int) + deriving (Eq) + + +instance Functor Get where + fmap p m = Get $ \ s0 b0 m0 kf ks -> + unGet m s0 b0 m0 kf $ \ s1 b1 m1 a -> ks s1 b1 m1 (p a) + +instance Applicative Get where + pure a = Get $ \ s0 b0 m0 _ ks -> ks s0 b0 m0 a + + f <*> x = Get $ \ s0 b0 m0 kf ks -> + unGet f s0 b0 m0 kf $ \ s1 b1 m1 g -> + unGet x s1 b1 m1 kf $ \ s2 b2 m2 y -> ks s2 b2 m2 (g y) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index a55df8e..daf22f6 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -1152,3 +1152,14 @@ test('Naperian', ], compile, ['']) + +test ('T9630', + [ compiler_stats_num_field('max_bytes_used', # Note [residency] + [(wordsize(64), 41568168, 15) + # initial: 56955240 + # 2017-06-07: 41568168 Stop the specialiser generating loopy code + ]), + extra_clean(['T9630a.hi', 'T9630a.o']) + ], + multimod_compile, + ['T9630', '-v0 -O']) From git at git.haskell.org Mon Jun 19 12:16:19 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 12:16:19 +0000 (UTC) Subject: [commit: ghc] master: Fix GCC 7 warning in the RTS (bea18a0) Message-ID: <20170619121619.502AE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bea18a0e9ea5ff2063ca4900acad9995f40276eb/ghc >--------------------------------------------------------------- commit bea18a0e9ea5ff2063ca4900acad9995f40276eb Author: Sylvain Henry Date: Sun Jun 18 16:50:09 2017 -0400 Fix GCC 7 warning in the RTS Test Plan: validate Reviewers: austin, bgamari, erikd, simonmar Reviewed By: bgamari, simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3648 >--------------------------------------------------------------- bea18a0e9ea5ff2063ca4900acad9995f40276eb rts/RtsFlags.c | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/rts/RtsFlags.c b/rts/RtsFlags.c index b51d644..73635cf 100644 --- a/rts/RtsFlags.c +++ b/rts/RtsFlags.c @@ -1559,6 +1559,10 @@ openStatsFile (char *filename, // filename, or NULL if (*filename != '\0') { /* stats file specified */ f = fopen(filename,"w"); } else { + if (filename_fmt == NULL) { + errorBelch("Invalid stats filename format (NULL)\n"); + return -1; + } /* default . */ char stats_filename[STATS_FILENAME_MAXLEN]; sprintf(stats_filename, filename_fmt, prog_name); From git at git.haskell.org Mon Jun 19 12:16:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 12:16:22 +0000 (UTC) Subject: [commit: ghc] master: cmm/CmmLayoutStack: avoid generating unnecessary reloads (6a2264d) Message-ID: <20170619121622.10F2E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6a2264d2bd47e993c43a592bd614ab7917184e22/ghc >--------------------------------------------------------------- commit 6a2264d2bd47e993c43a592bd614ab7917184e22 Author: Michal Terepeta Date: Sun Jun 18 16:51:08 2017 -0400 cmm/CmmLayoutStack: avoid generating unnecessary reloads This tries to be more precise when generating reloads of local registers in proc points. Previously we'd reload all local registers that were live. But we used liveness information that assumed local registers survive native calls. For the purpose of reloading registers this is an overapproximation and might lead to generating huge amounts of unnecessary reloads (in case there's another proc point before the register is used). This change takes the approach of moving the generation of reloads to a second pass over the Cmm, which allows to recompute the liveness and can use the knowledge that local registers do *not* survive calls. This leads to generating only useful reloads. For an extreme example where this helps a lot please see T3294. This should also fix #7198 Finally, this re-introduces the code to do Cmm rewriting using in `Dataflow` module (with the difference that we know operate on a whole block at a time). Signed-off-by: Michal Terepeta Reviewers: austin, bgamari, simonmar Reviewed By: simonmar Subscribers: kavon, rwbarton, thomie GHC Trac Issues: #7198 Differential Revision: https://phabricator.haskell.org/D3586 >--------------------------------------------------------------- 6a2264d2bd47e993c43a592bd614ab7917184e22 compiler/cmm/CmmLayoutStack.hs | 157 +++++++++++++++++++++++++++++------- compiler/cmm/Hoopl/Dataflow.hs | 115 +++++++++++++++++++++++++- testsuite/tests/perf/compiler/all.T | 19 +++-- 3 files changed, 253 insertions(+), 38 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 6a2264d2bd47e993c43a592bd614ab7917184e22 From git at git.haskell.org Mon Jun 19 12:16:24 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 12:16:24 +0000 (UTC) Subject: [commit: ghc] master: Don't expose fingerprints from Type.Reflection (990928f) Message-ID: <20170619121624.BCB303A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/990928ff463ef421842669ce56998d0fcfaa65c7/ghc >--------------------------------------------------------------- commit 990928ff463ef421842669ce56998d0fcfaa65c7 Author: David Feuer Date: Sun Jun 18 16:50:25 2017 -0400 Don't expose fingerprints from Type.Reflection The `Fingerprint` type is not exported from any "public" module. It therefore seems quite strange that `Type.Reflection` exports functions for extracting fingerprints. Remove those exports. If fingerprints are eventually considered public, this can be reconsidered. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3643 >--------------------------------------------------------------- 990928ff463ef421842669ce56998d0fcfaa65c7 libraries/base/Type/Reflection.hs | 3 --- 1 file changed, 3 deletions(-) diff --git a/libraries/base/Type/Reflection.hs b/libraries/base/Type/Reflection.hs index cb0337a..9e87c5f 100644 --- a/libraries/base/Type/Reflection.hs +++ b/libraries/base/Type/Reflection.hs @@ -40,7 +40,6 @@ module Type.Reflection , I.TypeRep , I.typeOf , pattern I.App, pattern I.Con, pattern I.Con', pattern I.Fun - , I.typeRepFingerprint , I.typeRepTyCon , I.rnfTypeRep , I.eqTypeRep @@ -54,7 +53,6 @@ module Type.Reflection , I.SomeTypeRep(..) , I.someTypeRep , I.someTypeRepTyCon - , I.someTypeRepFingerprint , I.rnfSomeTypeRep -- * Type constructors @@ -64,7 +62,6 @@ module Type.Reflection , I.tyConModule , I.tyConName , I.rnfTyCon - , I.tyConFingerprint -- * Module names , I.Module From git at git.haskell.org Mon Jun 19 12:16:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 12:16:27 +0000 (UTC) Subject: [commit: ghc] master: Add test cases for #13821 (271e0f0) Message-ID: <20170619121627.F0B293A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/271e0f087b6560f445d7e6bd7f6cecec917e1085/ghc >--------------------------------------------------------------- commit 271e0f087b6560f445d7e6bd7f6cecec917e1085 Author: Douglas Wilson Date: Sun Jun 18 16:50:38 2017 -0400 Add test cases for #13821 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13821 Differential Revision: https://phabricator.haskell.org/D3642 >--------------------------------------------------------------- 271e0f087b6560f445d7e6bd7f6cecec917e1085 testsuite/tests/typecheck/should_fail/Makefile | 4 ++++ testsuite/tests/typecheck/should_fail/T13821A.hs-boot | 6 ++++++ testsuite/tests/typecheck/should_fail/T13821B.bkp | 6 ++++++ testsuite/tests/typecheck/should_fail/all.T | 2 ++ 4 files changed, 18 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/Makefile b/testsuite/tests/typecheck/should_fail/Makefile index f994435..2c5e874 100644 --- a/testsuite/tests/typecheck/should_fail/Makefile +++ b/testsuite/tests/typecheck/should_fail/Makefile @@ -6,3 +6,7 @@ include $(TOP)/mk/test.mk foo: echo hello + +T13821A: + $(RM) -f T13821A.hi-boot T13821A.o-boot + !('$(TEST_HC)' $(TEST_HC_OPTS) -c T13821A.hs-boot) diff --git a/testsuite/tests/typecheck/should_fail/T13821A.hs-boot b/testsuite/tests/typecheck/should_fail/T13821A.hs-boot new file mode 100644 index 0000000..4fda6bc --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T13821A.hs-boot @@ -0,0 +1,6 @@ +{-# LANGUAGE MagicHash #-} +module T13821A where + +import GHC.Prim + +x :: Int# diff --git a/testsuite/tests/typecheck/should_fail/T13821B.bkp b/testsuite/tests/typecheck/should_fail/T13821B.bkp new file mode 100644 index 0000000..8d5e066 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T13821B.bkp @@ -0,0 +1,6 @@ +{-# LANGUAGE MagicHash #-} +unit T13821B where + signature A where + import GHC.Prim + + x :: Int# \ No newline at end of file diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index bf4854f..5cc8171 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -442,3 +442,5 @@ test('T13611', expect_broken(13611), compile_fail, ['']) test('T13320', normal, compile_fail, ['']) test('T13640', normal, compile_fail, ['']) test('T13677', normal, compile_fail, ['']) +test('T13821A', expect_broken(13821), run_command, ['$MAKE -s --no-print-directory T13821A']) +test('T13821B', expect_broken(13821), backpack_typecheck_fail, ['']) From git at git.haskell.org Mon Jun 19 12:16:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 12:16:30 +0000 (UTC) Subject: [commit: ghc] master: configure: Look for objdump on OpenBSD and AIX (a9b62a3) Message-ID: <20170619121630.AE3E43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a9b62a3e883e536724602bce2a5bb8a21eba02cc/ghc >--------------------------------------------------------------- commit a9b62a3e883e536724602bce2a5bb8a21eba02cc Author: Ben Gamari Date: Sun Jun 18 16:50:51 2017 -0400 configure: Look for objdump on OpenBSD and AIX deriveConstants requires objdump for both of these operating systems, in addition to Windows. See #13812. Test Plan: Validate on OpenBSD and AIX Reviewers: hvr, austin Reviewed By: hvr Subscribers: rwbarton, thomie, erikd GHC Trac Issues: #13812 Differential Revision: https://phabricator.haskell.org/D3638 >--------------------------------------------------------------- a9b62a3e883e536724602bce2a5bb8a21eba02cc configure.ac | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/configure.ac b/configure.ac index d7c6ad8..3c5e17a 100644 --- a/configure.ac +++ b/configure.ac @@ -565,9 +565,10 @@ fi dnl ** Which objdump to use? dnl -------------------------------------------------------------- -dnl Note: we may not have objdump on OS X, and we only need it on Windows (for DLL checks) +dnl Note: we may not have objdump on OS X, and we only need it on +dnl Windows (for DLL checks), OpenBSD, and AIX case $HostOS_CPP in - cygwin32|mingw32) + cygwin32|mingw32|openbsd|aix) AC_CHECK_TARGET_TOOL([OBJDUMP], [objdump]) ;; esac From git at git.haskell.org Mon Jun 19 13:03:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 13:03:30 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump Cabal submodule to 2.0.0.1 (1ab05da) Message-ID: <20170619130330.3419C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/1ab05dac3c42d5873b6fdfda84abce56f44c2618/ghc >--------------------------------------------------------------- commit 1ab05dac3c42d5873b6fdfda84abce56f44c2618 Author: Ben Gamari Date: Sun Jun 11 21:47:05 2017 -0400 Bump Cabal submodule to 2.0.0.1 >--------------------------------------------------------------- 1ab05dac3c42d5873b6fdfda84abce56f44c2618 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index ece0273..3aa2d69 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit ece0273b48b7ff19fff6cd82913717d86d3ffbfa +Subproject commit 3aa2d69f12409ac675d5415dd1c3ef2db8e1b9e6 From git at git.haskell.org Mon Jun 19 13:03:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 13:03:32 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Make GHCi work when RebindableSyntax is enabled (c89ef44) Message-ID: <20170619130332.DF4663A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/c89ef44bbf8c11fca9a12d8fc52c57b382055630/ghc >--------------------------------------------------------------- commit c89ef44bbf8c11fca9a12d8fc52c57b382055630 Author: Ryan Scott Date: Fri Jun 2 11:49:47 2017 -0400 Make GHCi work when RebindableSyntax is enabled Previously, we were running some blocks of code at the start of every GHCi sessions which use do-notation, something which doesn't work well if you start GHCi with the `-XRebindableSyntax` flag on. This tweaks the code to avoid the use of do-notation so that `-XRebindableSyntax` won't reject it. Test Plan: make test TEST=T13385 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13385 Differential Revision: https://phabricator.haskell.org/D3621 (cherry picked from commit 2abe54e16cbd14cab27abdc7967e907753354d54) >--------------------------------------------------------------- c89ef44bbf8c11fca9a12d8fc52c57b382055630 ghc/GHCi/UI/Monad.hs | 12 +++++++----- .../tests/ghci/scripts/T13385.script | 0 testsuite/tests/ghci/scripts/all.T | 1 + 3 files changed, 8 insertions(+), 5 deletions(-) diff --git a/ghc/GHCi/UI/Monad.hs b/ghc/GHCi/UI/Monad.hs index 244595b..b57a5a0 100644 --- a/ghc/GHCi/UI/Monad.hs +++ b/ghc/GHCi/UI/Monad.hs @@ -420,13 +420,15 @@ foreign import ccall "revertCAFs" rts_revertCAFs :: IO () -- | Compile "hFlush stdout; hFlush stderr" once, so we can use it repeatedly initInterpBuffering :: Ghc (ForeignHValue, ForeignHValue) initInterpBuffering = do + -- We take great care not to use do-notation in the expressions below, as + -- they are fragile in the presence of RebindableSyntax (Trac #13385). nobuf <- GHC.compileExprRemote $ - "do { System.IO.hSetBuffering System.IO.stdin System.IO.NoBuffering; " ++ - " System.IO.hSetBuffering System.IO.stdout System.IO.NoBuffering; " ++ - " System.IO.hSetBuffering System.IO.stderr System.IO.NoBuffering }" + " System.IO.hSetBuffering System.IO.stdin System.IO.NoBuffering" ++ + "`GHC.Base.thenIO` System.IO.hSetBuffering System.IO.stdout System.IO.NoBuffering" ++ + "`GHC.Base.thenIO` System.IO.hSetBuffering System.IO.stderr System.IO.NoBuffering" flush <- GHC.compileExprRemote $ - "do { System.IO.hFlush System.IO.stdout; " ++ - " System.IO.hFlush System.IO.stderr }" + " System.IO.hFlush System.IO.stdout" ++ + "`GHC.Base.thenIO` System.IO.hFlush System.IO.stderr" return (nobuf, flush) -- | Invoke "hFlush stdout; hFlush stderr" in the interpreter diff --git a/libraries/ghc-compact/tests/compact_serialize.stderr b/testsuite/tests/ghci/scripts/T13385.script similarity index 100% copy from libraries/ghc-compact/tests/compact_serialize.stderr copy to testsuite/tests/ghci/scripts/T13385.script diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 77b611a..71f812f 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -251,5 +251,6 @@ test('T12550', normal, ghci_script, ['T12550.script']) test('StaticPtr', normal, ghci_script, ['StaticPtr.script']) test('T13202', normal, ghci_script, ['T13202.script']) test('T13202a', normal, ghci_script, ['T13202a.script']) +test('T13385', [extra_hc_opts("-XRebindableSyntax")], ghci_script, ['T13385.script']) test('T13466', normal, ghci_script, ['T13466.script']) test('GhciCurDir', normal, ghci_script, ['GhciCurDir.script']) From git at git.haskell.org Mon Jun 19 13:03:35 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 13:03:35 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Typofix in Data.Type.Equality comments (7941f2f) Message-ID: <20170619130335.98D5F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/7941f2f7c26f91a9fbad93aa3577ef2d97bc3d23/ghc >--------------------------------------------------------------- commit 7941f2f7c26f91a9fbad93aa3577ef2d97bc3d23 Author: Ryan Scott Date: Sun Jun 18 14:30:38 2017 -0400 Typofix in Data.Type.Equality comments (cherry picked from commit df3288000e860856f0fe0ffe67669da9ae5a0a03) >--------------------------------------------------------------- 7941f2f7c26f91a9fbad93aa3577ef2d97bc3d23 libraries/base/Data/Type/Equality.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/Data/Type/Equality.hs b/libraries/base/Data/Type/Equality.hs index bd597ee..8cc34f6 100644 --- a/libraries/base/Data/Type/Equality.hs +++ b/libraries/base/Data/Type/Equality.hs @@ -112,7 +112,7 @@ gcastWith Refl x = x apply :: (f :~: g) -> (a :~: b) -> (f a :~: g b) apply Refl Refl = Refl --- | Extract equality of the arguments from an equality of a applied types +-- | Extract equality of the arguments from an equality of applied types inner :: (f a :~: g b) -> (a :~: b) inner Refl = Refl From git at git.haskell.org Mon Jun 19 13:03:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 13:03:38 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Add fixity declaration for :~~: (e4925da) Message-ID: <20170619130338.5740C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/e4925dab854c9482cd621e6a649b4b2a5fe8016a/ghc >--------------------------------------------------------------- commit e4925dab854c9482cd621e6a649b4b2a5fe8016a Author: Ryan Scott Date: Sun Jun 18 16:49:02 2017 -0400 Add fixity declaration for :~~: We have one for `(:~:)`, but not for `(:~~:)`! Let's fix this oversight. Reviewers: bgamari, austin, hvr Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3657 (cherry picked from commit ee9232524bdba5b268278ec51f30106bb7178ce9) >--------------------------------------------------------------- e4925dab854c9482cd621e6a649b4b2a5fe8016a libraries/base/Data/Type/Equality.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/Data/Type/Equality.hs b/libraries/base/Data/Type/Equality.hs index 69da70b..bd597ee 100644 --- a/libraries/base/Data/Type/Equality.hs +++ b/libraries/base/Data/Type/Equality.hs @@ -77,7 +77,7 @@ instance {-# INCOHERENT #-} a ~~ b => a ~ b -- INCOHERENT because we want to use this instance eagerly, even when -- the tyvars are partially unknown. -infix 4 :~: +infix 4 :~:, :~~: -- | Propositional equality. If @a :~: b@ is inhabited by some terminating -- value, then the type @a@ is the same as the type @b at . To use this equality From git at git.haskell.org Mon Jun 19 13:03:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 13:03:41 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Don't expose fingerprints from Type.Reflection (83a6dd8) Message-ID: <20170619130341.1433B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/83a6dd82a883ef1d173bbc3b70af8265e298ab94/ghc >--------------------------------------------------------------- commit 83a6dd82a883ef1d173bbc3b70af8265e298ab94 Author: David Feuer Date: Sun Jun 18 16:50:25 2017 -0400 Don't expose fingerprints from Type.Reflection The `Fingerprint` type is not exported from any "public" module. It therefore seems quite strange that `Type.Reflection` exports functions for extracting fingerprints. Remove those exports. If fingerprints are eventually considered public, this can be reconsidered. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3643 (cherry picked from commit 990928ff463ef421842669ce56998d0fcfaa65c7) >--------------------------------------------------------------- 83a6dd82a883ef1d173bbc3b70af8265e298ab94 libraries/base/Type/Reflection.hs | 3 --- 1 file changed, 3 deletions(-) diff --git a/libraries/base/Type/Reflection.hs b/libraries/base/Type/Reflection.hs index cb0337a..9e87c5f 100644 --- a/libraries/base/Type/Reflection.hs +++ b/libraries/base/Type/Reflection.hs @@ -40,7 +40,6 @@ module Type.Reflection , I.TypeRep , I.typeOf , pattern I.App, pattern I.Con, pattern I.Con', pattern I.Fun - , I.typeRepFingerprint , I.typeRepTyCon , I.rnfTypeRep , I.eqTypeRep @@ -54,7 +53,6 @@ module Type.Reflection , I.SomeTypeRep(..) , I.someTypeRep , I.someTypeRepTyCon - , I.someTypeRepFingerprint , I.rnfSomeTypeRep -- * Type constructors @@ -64,7 +62,6 @@ module Type.Reflection , I.tyConModule , I.tyConName , I.rnfTyCon - , I.tyConFingerprint -- * Module names , I.Module From git at git.haskell.org Mon Jun 19 14:59:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 14:59:33 +0000 (UTC) Subject: [commit: ghc] master: Reword documentation region overlap documentation for copying mutable arrays (564a31f) Message-ID: <20170619145933.A8EA23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/564a31f32e522398c50828bcf35cf8deeec5e654/ghc >--------------------------------------------------------------- commit 564a31f32e522398c50828bcf35cf8deeec5e654 Author: Andrew Martin Date: Sat Jun 17 17:35:32 2017 -0400 Reword documentation region overlap documentation for copying mutable arrays >--------------------------------------------------------------- 564a31f32e522398c50828bcf35cf8deeec5e654 compiler/prelude/primops.txt.pp | 20 ++++++++++++++------ 1 file changed, 14 insertions(+), 6 deletions(-) diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp index bff4540..97ae89c 100644 --- a/compiler/prelude/primops.txt.pp +++ b/compiler/prelude/primops.txt.pp @@ -825,9 +825,10 @@ primop CopyMutableArrayOp "copyMutableArray#" GenPrimOp {Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array - to the destination array. The source and destination arrays can - refer to the same array. Both arrays must fully contain the - specified ranges, but this is not checked.} + to the destination array. Both arrays must fully contain the + specified ranges, but this is not checked. In the case where + the source and destination are the same array the source and + destination regions may overlap.} with out_of_line = True has_side_effects = True @@ -990,7 +991,9 @@ primop CopySmallMutableArrayOp "copySmallMutableArray#" GenPrimOp number of elements to copy, copy the elements from the source array to the destination array. The source and destination arrays can refer to the same array. Both arrays must fully contain the - specified ranges, but this is not checked.} + specified ranges, but this is not checked. + The regions are allowed to overlap, although this is only possible when the same + array is provided as both the source and the destination. } with out_of_line = True has_side_effects = True @@ -1400,7 +1403,9 @@ primop CopyByteArrayOp "copyByteArray#" GenPrimOp primop CopyMutableByteArrayOp "copyMutableByteArray#" GenPrimOp MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s {Copy a range of the first MutableByteArray# to the specified region in the second MutableByteArray#. - Both arrays must fully contain the specified ranges, but this is not checked.} + Both arrays must fully contain the specified ranges, but this is not checked. The regions are + allowed to overlap, although this is only possible when the same array is provided + as both the source and the destination.} with has_side_effects = True code_size = { primOpCodeSizeForeignCall + 4 } @@ -1627,7 +1632,10 @@ primop CopyMutableArrayArrayOp "copyMutableArrayArray#" GenPrimOp MutableArrayArray# s -> Int# -> MutableArrayArray# s -> Int# -> Int# -> State# s -> State# s {Copy a range of the first MutableArrayArray# to the specified region in the second MutableArrayArray#. - Both arrays must fully contain the specified ranges, but this is not checked.} + Both arrays must fully contain the specified ranges, but this is not checked. + The regions are allowed to overlap, although this is only possible when the same + array is provided as both the source and the destination. + } with out_of_line = True has_side_effects = True From git at git.haskell.org Mon Jun 19 14:59:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 14:59:36 +0000 (UTC) Subject: [commit: ghc] master: Add missing -Wdeprecations flag to the users guide (986deaa) Message-ID: <20170619145936.7BDFE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/986deaa5539552f84b4f1d1872ae8a4c8240097e/ghc >--------------------------------------------------------------- commit 986deaa5539552f84b4f1d1872ae8a4c8240097e Author: erdeszt Date: Sat Jun 17 13:47:10 2017 +0200 Add missing -Wdeprecations flag to the users guide >--------------------------------------------------------------- 986deaa5539552f84b4f1d1872ae8a4c8240097e docs/users_guide/using-warnings.rst | 13 +++++++++++++ utils/mkUserGuidePart/Options/Warnings.hs | 7 +++++++ 2 files changed, 20 insertions(+) diff --git a/docs/users_guide/using-warnings.rst b/docs/users_guide/using-warnings.rst index 9bc1c35..9f10efb 100644 --- a/docs/users_guide/using-warnings.rst +++ b/docs/users_guide/using-warnings.rst @@ -17,6 +17,7 @@ generally likely to indicate bugs in your program. These are: * :ghc-flag:`-Woverlapping-patterns` * :ghc-flag:`-Wwarnings-deprecations` + * :ghc-flag:`-Wdeprecations` * :ghc-flag:`-Wdeprecated-flags` * :ghc-flag:`-Wunrecognised-pragmas` * :ghc-flag:`-Wduplicate-constraints` @@ -246,6 +247,18 @@ of ``-W(no-)*``. This option is on by default. +.. ghc-flag:: -Wdeprecations + + .. index:: + single: deprecations + + Causes a warning to be emitted when a module, function or type with + a ``WARNING`` or ``DEPRECATED pragma`` is used. See + :ref:`warning-deprecated-pragma` for more details on the pragmas. + An alias for :ghc-flag:`-Wwarnings-deprecations`. + + This option is on by default. + .. ghc-flag:: -Wamp .. index:: diff --git a/utils/mkUserGuidePart/Options/Warnings.hs b/utils/mkUserGuidePart/Options/Warnings.hs index 48ee32c..620c731 100644 --- a/utils/mkUserGuidePart/Options/Warnings.hs +++ b/utils/mkUserGuidePart/Options/Warnings.hs @@ -401,6 +401,13 @@ warningsOptions = , flagType = DynamicFlag , flagReverse = "-Wno-warnings-deprecations" } + , flag { flagName = "-Wdeprecations" + , flagDescription = + "warn about uses of functions & types that have warnings or "++ + "deprecated pragmas. Alias for :ghc-flag:`-Wwarnings-deprecations`" + , flagType = DynamicFlag + , flagReverse = "-Wno-deprecations" + } , flag { flagName = "-Wamp" , flagDescription = "*(deprecated)* warn on definitions conflicting with the "++ From git at git.haskell.org Mon Jun 19 16:40:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 16:40:16 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Enable win64 again (7ed6da0) Message-ID: <20170619164016.6C6DD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/7ed6da0d4ec7c224848936c05704c6f84323a20b/ghc >--------------------------------------------------------------- commit 7ed6da0d4ec7c224848936c05704c6f84323a20b Author: Ben Gamari Date: Mon Jun 19 12:39:58 2017 -0400 Enable win64 again >--------------------------------------------------------------- 7ed6da0d4ec7c224848936c05704c6f84323a20b 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 Mon Jun 19 21:43:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jun 2017 21:43:38 +0000 (UTC) Subject: [commit: ghc] master: Improve comments on AbsBinds (5c93df9) Message-ID: <20170619214338.61AC23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5c93df90a96494229b60bbed0971a4b08c0326a6/ghc >--------------------------------------------------------------- commit 5c93df90a96494229b60bbed0971a4b08c0326a6 Author: Simon Peyton Jones Date: Mon Jun 19 11:50:37 2017 +0100 Improve comments on AbsBinds See Trac #13827. >--------------------------------------------------------------- 5c93df90a96494229b60bbed0971a4b08c0326a6 compiler/hsSyn/HsBinds.hs | 91 ++++++++++++++++++++++++++++------------------- 1 file changed, 55 insertions(+), 36 deletions(-) diff --git a/compiler/hsSyn/HsBinds.hs b/compiler/hsSyn/HsBinds.hs index b760cb3..d0c345a 100644 --- a/compiler/hsSyn/HsBinds.hs +++ b/compiler/hsSyn/HsBinds.hs @@ -301,15 +301,57 @@ deriving instance (DataId idL, DataId idR) => Data (PatSynBind idL idR) {- Note [AbsBinds] ~~~~~~~~~~~~~~~ -The AbsBinds constructor is used in the output of the type checker, to record -*typechecked* and *generalised* bindings. Consider a module M, with this -top-level binding, where there is no type signature for M.reverse, +The AbsBinds constructor is used in the output of the type checker, to +record *typechecked* and *generalised* bindings. Specifically + + AbsBinds { abs_tvs = tvs + , abs_ev_vars = [d1,d2] + , abs_exports = [ABE { abe_poly = fp, abe_mono = fm + , abe_wrap = fwrap } + ABE { slly for g } ] + , abs_ev_binds = DBINDS + , abs_binds = BIND[fm,gm] } + +where 'BIND' binds the monomorphic Ids 'fm' and 'gm', means + + fp = fwrap [/\ tvs. \d1 d2. letrec { DBINDS ] + [ ; BIND[fm,gm] } ] + [ in fm ] + + gp = ...same again, with gm instead of fm + +The 'fwrap' is an impedence-matcher that typically does nothing; see +Note [ABExport wrapper]. + +This is a pretty bad translation, because it duplicates all the bindings. +So the desugarer tries to do a better job: + + fp = /\ [a,b] -> \ [d1,d2] -> case tp [a,b] [d1,d2] of + (fm,gm) -> fm + ..ditto for gp.. + + tp = /\ [a,b] -> \ [d1,d2] -> letrec { DBINDS; BIND } + in (fm,gm) + +In general: + + * abs_tvs are the type variables over which the binding group is + generalised + * abs_ev_var are the evidence variables (usually dictionaries) + over which the binding group is generalised + * abs_binds are the monomorphic bindings + * abs_ex_binds are the evidence bindings that wrap the abs_binds + * abs_exports connects the monomorphic Ids bound by abs_binds + with the polymorphic Ids bound by the AbsBinds itself. + +For example, consider a module M, with this top-level binding, where +there is no type signature for M.reverse, M.reverse [] = [] M.reverse (x:xs) = M.reverse xs ++ [x] -In Hindley-Milner, a recursive binding is typechecked with the *recursive* uses -being *monomorphic*. So after typechecking *and* desugaring we will get something -like this +In Hindley-Milner, a recursive binding is typechecked with the +*recursive* uses being *monomorphic*. So after typechecking *and* +desugaring we will get something like this M.reverse :: forall a. [a] -> [a] = /\a. letrec @@ -326,19 +368,22 @@ That's after desugaring. What about after type checking but before desugaring? That's where AbsBinds comes in. It looks like this: AbsBinds { abs_tvs = [a] + , abs_ev_vars = [] , abs_exports = [ABE { abe_poly = M.reverse :: forall a. [a] -> [a], , abe_mono = reverse :: [a] -> [a]}] + , abs_ev_binds = {} , abs_binds = { reverse :: [a] -> [a] = \xs -> case xs of [] -> [] (x:xs) -> reverse xs ++ [x] } } Here, - * abs_tvs says what type variables are abstracted over the binding group, - just 'a' in this case. + + * abs_tvs says what type variables are abstracted over the binding + group, just 'a' in this case. * abs_binds is the *monomorphic* bindings of the group - * abs_exports describes how to get the polymorphic Id 'M.reverse' from the - monomorphic one 'reverse' + * abs_exports describes how to get the polymorphic Id 'M.reverse' + from the monomorphic one 'reverse' Notice that the *original* function (the polymorphic one you thought you were defining) appears in the abe_poly field of the @@ -537,32 +582,6 @@ plusHsValBinds (ValBindsOut ds1 sigs1) (ValBindsOut ds2 sigs2) plusHsValBinds _ _ = panic "HsBinds.plusHsValBinds" -{- -What AbsBinds means -~~~~~~~~~~~~~~~~~~~ - AbsBinds tvs - [d1,d2] - [(tvs1, f1p, f1m), - (tvs2, f2p, f2m)] - BIND -means - - f1p = /\ tvs -> \ [d1,d2] -> letrec DBINDS and BIND - in fm - - gp = ...same again, with gm instead of fm - -This is a pretty bad translation, because it duplicates all the bindings. -So the desugarer tries to do a better job: - - fp = /\ [a,b] -> \ [d1,d2] -> case tp [a,b] [d1,d2] of - (fm,gm) -> fm - ..ditto for gp.. - - tp = /\ [a,b] -> \ [d1,d2] -> letrec DBINDS and BIND - in (fm,gm) --} - instance (SourceTextX idL, SourceTextX idR, OutputableBndrId idL, OutputableBndrId idR) => Outputable (HsBindLR idL idR) where From git at git.haskell.org Tue Jun 20 10:01:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Jun 2017 10:01:09 +0000 (UTC) Subject: [commit: ghc] master: Fix note reference [ci skip] (b1fa386) Message-ID: <20170620100109.DE9723A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b1fa386cdae1af45fdd3519014be850f83414ab3/ghc >--------------------------------------------------------------- commit b1fa386cdae1af45fdd3519014be850f83414ab3 Author: Gabor Greif Date: Tue Jun 20 12:00:30 2017 +0200 Fix note reference [ci skip] >--------------------------------------------------------------- b1fa386cdae1af45fdd3519014be850f83414ab3 compiler/typecheck/TcSMonad.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index bb305ed..473f325 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -292,7 +292,7 @@ extendWorkListCt ct wl EqPred {} -> extendWorkListEq ct wl - ClassPred cls _ -- See Note [Prioritise class equalites] + ClassPred cls _ -- See Note [Prioritise class equalities] | cls `hasKey` heqTyConKey || cls `hasKey` eqTyConKey -> extendWorkListEq ct wl From git at git.haskell.org Wed Jun 21 20:28:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Jun 2017 20:28:32 +0000 (UTC) Subject: [commit: ghc] master: UNREG: use __builtin___clear_cache where available (6dd1257) Message-ID: <20170621202832.5A1203A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6dd1257fdd4d18e84d32e89bf0ec664b3c8f7b93/ghc >--------------------------------------------------------------- commit 6dd1257fdd4d18e84d32e89bf0ec664b3c8f7b93 Author: Sergei Trofimovich Date: Wed Jun 21 21:17:51 2017 +0100 UNREG: use __builtin___clear_cache where available Noticed when was building UNREG ghc with -optc{-Wall,-Werror}: rts/sm/Storage.c:1359:3: error: error: implicit declaration of function '__clear_cache' [-Werror=implicit-function-declaration] __clear_cache((void*)begin, (void*)end); ^~~~~~~~~~~~~ | 1359 | __clear_cache((void*)begin, (void*)end); | ^ Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 6dd1257fdd4d18e84d32e89bf0ec664b3c8f7b93 rts/sm/Storage.c | 22 +++++++++++++++++++++- 1 file changed, 21 insertions(+), 1 deletion(-) diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c index 4aa4b12..2e2834b 100644 --- a/rts/sm/Storage.c +++ b/rts/sm/Storage.c @@ -1341,6 +1341,26 @@ StgWord calcTotalCompactW (void) #include #endif +#if defined(__GNUC__) +/* __clear_cache is a libgcc function. + * It existed before __builtin___clear_cache was introduced. + * See Trac #8562. + */ +extern void __clear_cache(char * begin, char * end); + +STATIC_INLINE void gcc_clear_cache(void * begin, void * end) +{ + /* __builtin___clear_cache is supported since GNU C 4.3.6. + * We pick 4.4 to simplify condition a bit. + */ +#if __GNUC__ > 4 || (__GNUC__ == 4 && __GNUC_MINOR__ >= 4) + __builtin___clear_cache(begin, end); +#else + __clear_cache(begin, end); +#endif +} +#endif /* __GNUC__ */ + /* On ARM and other platforms, we need to flush the cache after writing code into memory, so the processor reliably sees it. */ void flushExec (W_ len, AdjustorExecutable exec_addr) @@ -1356,7 +1376,7 @@ void flushExec (W_ len, AdjustorExecutable exec_addr) /* For all other platforms, fall back to a libgcc builtin. */ unsigned char* begin = (unsigned char*)exec_addr; unsigned char* end = begin + len; - __clear_cache((void*)begin, (void*)end); + gcc_clear_cache((void*)begin, (void*)end); #else #error Missing support to flush the instruction cache #endif From git at git.haskell.org Wed Jun 21 20:36:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Jun 2017 20:36:41 +0000 (UTC) Subject: [commit: ghc] master: base: Export Fingerprint accessors from Type.Reflection.Unsafe (88263f9) Message-ID: <20170621203641.6DB2D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/88263f93e0f3add38f925d5afb799eee8df32606/ghc >--------------------------------------------------------------- commit 88263f93e0f3add38f925d5afb799eee8df32606 Author: Ben Gamari Date: Tue Jun 20 14:59:40 2017 -0400 base: Export Fingerprint accessors from Type.Reflection.Unsafe Reviewers: dfeuer, austin, hvr Reviewed By: dfeuer Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3660 >--------------------------------------------------------------- 88263f93e0f3add38f925d5afb799eee8df32606 libraries/base/Type/Reflection/Unsafe.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/base/Type/Reflection/Unsafe.hs b/libraries/base/Type/Reflection/Unsafe.hs index 4cffd89..c0f2327 100644 --- a/libraries/base/Type/Reflection/Unsafe.hs +++ b/libraries/base/Type/Reflection/Unsafe.hs @@ -15,11 +15,11 @@ module Type.Reflection.Unsafe ( -- * Type representations - TypeRep, mkTrApp, mkTyCon + TypeRep, mkTrApp, mkTyCon, typeRepFingerprint, someTypeRepFingerprint -- * Kind representations , KindRep(..), TypeLitSort(..) -- * Type constructors - , TyCon, mkTrCon, tyConKindRep, tyConKindArgs, + , TyCon, mkTrCon, tyConKindRep, tyConKindArgs, tyConFingerprint ) where import Data.Typeable.Internal From git at git.haskell.org Wed Jun 21 20:36:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Jun 2017 20:36:47 +0000 (UTC) Subject: [commit: ghc] master: change filtering of variables in extract_hs_tv_bndrs (fixes #13782) (c8370a8) Message-ID: <20170621203647.A4EC83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c8370a821bb92ca3846953cb0b37250720087135/ghc >--------------------------------------------------------------- commit c8370a821bb92ca3846953cb0b37250720087135 Author: Carlos Tomé Date: Tue Jun 20 15:00:46 2017 -0400 change filtering of variables in extract_hs_tv_bndrs (fixes #13782) Reviewers: austin, bgamari, goldfire Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13782 Differential Revision: https://phabricator.haskell.org/D3641 >--------------------------------------------------------------- c8370a821bb92ca3846953cb0b37250720087135 compiler/rename/RnTypes.hs | 107 +++++++++++-------------------------------- testsuite/tests/th/T13782.hs | 14 ++++++ testsuite/tests/th/all.T | 1 + 3 files changed, 43 insertions(+), 79 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c8370a821bb92ca3846953cb0b37250720087135 From git at git.haskell.org Wed Jun 21 20:36:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Jun 2017 20:36:44 +0000 (UTC) Subject: [commit: ghc] master: Show only the number of modules in ghci (c85cd9b) Message-ID: <20170621203644.403983A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c85cd9b2ff74c42f02a65edd74949267710f02f4/ghc >--------------------------------------------------------------- commit c85cd9b2ff74c42f02a65edd74949267710f02f4 Author: Francesco Mazzoli Date: Tue Jun 20 15:00:20 2017 -0400 Show only the number of modules in ghci Reviewers: bgamari, austin, simonmar Reviewed By: bgamari Subscribers: mpickering, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3651 >--------------------------------------------------------------- c85cd9b2ff74c42f02a65edd74949267710f02f4 ghc/GHCi/UI.hs | 27 +++++++++------------------ testsuite/tests/driver/T8526/T8526.stdout | 4 ++-- testsuite/tests/ghci/scripts/T1914.stdout | 6 +++--- testsuite/tests/ghci/scripts/T6105.stdout | 4 ++-- testsuite/tests/ghci/scripts/ghci058.stdout | 4 ++-- 5 files changed, 18 insertions(+), 27 deletions(-) diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs index d502fb8..40bd0e5 100644 --- a/ghc/GHCi/UI.hs +++ b/ghc/GHCi/UI.hs @@ -51,7 +51,7 @@ import GHC ( LoadHowMuch(..), Target(..), TargetId(..), InteractiveImport(..), import HsImpExp import HsSyn import HscTypes ( tyThingParent_maybe, handleFlagWarnings, getSafeMode, hsc_IC, - setInteractivePrintName, hsc_dflags, msObjFilePath ) + setInteractivePrintName, hsc_dflags ) import Module import Name import Packages ( trusted, getPackageDetails, getInstalledPackageDetails, @@ -1721,7 +1721,7 @@ afterLoad ok retain_context = do lift revertCAFs -- always revert CAFs on load. lift discardTickArrays loaded_mods <- getLoadedModules - modulesLoadedMsg ok loaded_mods + modulesLoadedMsg ok (length loaded_mods) lift $ setContextAfterLoad retain_context loaded_mods setContextAfterLoad :: Bool -> [GHC.ModSummary] -> GHCi () @@ -1796,27 +1796,18 @@ keepPackageImports = filterM is_pkg_import mod_name = unLoc (ideclName d) -modulesLoadedMsg :: SuccessFlag -> [GHC.ModSummary] -> InputT GHCi () -modulesLoadedMsg ok mods = do +modulesLoadedMsg :: SuccessFlag -> Int -> InputT GHCi () +modulesLoadedMsg ok num_mods = do dflags <- getDynFlags unqual <- GHC.getPrintUnqual - let mod_name mod = do - is_interpreted <- GHC.moduleIsBootOrNotObjectLinkable mod - return $ if is_interpreted - then ppr (GHC.ms_mod mod) - else ppr (GHC.ms_mod mod) - <> text " (" - <> text (normalise $ msObjFilePath mod) - <> text ")" -- fix #9887 - mod_names <- mapM mod_name mods - let mod_commas - | null mods = text "none." - | otherwise = hsep (punctuate comma mod_names) <> text "." - status = case ok of + let status = case ok of Failed -> text "Failed" Succeeded -> text "Ok" - msg = status <> text ", modules loaded:" <+> mod_commas + num_mods_pp = if num_mods == 1 + then "1 module" + else int num_mods <+> "modules" + msg = status <> text "," <+> num_mods_pp <+> "loaded." when (verbosity dflags > 0) $ liftIO $ putStrLn $ showSDocForUser dflags unqual msg diff --git a/testsuite/tests/driver/T8526/T8526.stdout b/testsuite/tests/driver/T8526/T8526.stdout index 3b24506..83b8f95 100644 --- a/testsuite/tests/driver/T8526/T8526.stdout +++ b/testsuite/tests/driver/T8526/T8526.stdout @@ -1,6 +1,6 @@ [1 of 1] Compiling A ( A.hs, interpreted ) -Ok, modules loaded: A. +Ok, 1 module loaded. True [1 of 1] Compiling A ( A.hs, interpreted ) -Ok, modules loaded: A. +Ok, 1 module loaded. False diff --git a/testsuite/tests/ghci/scripts/T1914.stdout b/testsuite/tests/ghci/scripts/T1914.stdout index 063758e..2d1a82b 100644 --- a/testsuite/tests/ghci/scripts/T1914.stdout +++ b/testsuite/tests/ghci/scripts/T1914.stdout @@ -1,7 +1,7 @@ [1 of 2] Compiling T1914B ( T1914B.hs, interpreted ) [2 of 2] Compiling T1914A ( T1914A.hs, interpreted ) -Ok, modules loaded: T1914A, T1914B. +Ok, 2 modules loaded. [2 of 2] Compiling T1914A ( T1914A.hs, interpreted ) -Failed, modules loaded: T1914B. +Failed, 1 module loaded. [2 of 2] Compiling T1914A ( T1914A.hs, interpreted ) -Ok, modules loaded: T1914A, T1914B. +Ok, 2 modules loaded. diff --git a/testsuite/tests/ghci/scripts/T6105.stdout b/testsuite/tests/ghci/scripts/T6105.stdout index 73b6d2c..6a846e3 100644 --- a/testsuite/tests/ghci/scripts/T6105.stdout +++ b/testsuite/tests/ghci/scripts/T6105.stdout @@ -1,4 +1,4 @@ [1 of 1] Compiling T6105 ( T6105.hs, interpreted ) -Ok, modules loaded: T6105. +Ok, 1 module loaded. [1 of 1] Compiling T6105 ( T6105.hs, interpreted ) -Ok, modules loaded: T6105. +Ok, 1 module loaded. diff --git a/testsuite/tests/ghci/scripts/ghci058.stdout b/testsuite/tests/ghci/scripts/ghci058.stdout index bc77f05..2028aee 100644 --- a/testsuite/tests/ghci/scripts/ghci058.stdout +++ b/testsuite/tests/ghci/scripts/ghci058.stdout @@ -1,4 +1,4 @@ -Ok, modules loaded: Ghci058 (Ghci058.o). +Ok, 1 module loaded. 'a' -Ok, modules loaded: Ghci058 (Ghci058.o). +Ok, 1 module loaded. 'b' From git at git.haskell.org Wed Jun 21 21:16:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Jun 2017 21:16:48 +0000 (UTC) Subject: [commit: ghc] master: Revert "UNREG: use __builtin___clear_cache where available" (c6fe403) Message-ID: <20170621211648.CE9603A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c6fe403ec714bf29cad9d94196f0db3c80a02235/ghc >--------------------------------------------------------------- commit c6fe403ec714bf29cad9d94196f0db3c80a02235 Author: Sergei Trofimovich Date: Wed Jun 21 22:15:22 2017 +0100 Revert "UNREG: use __builtin___clear_cache where available" This reverts commit 6dd1257fdd4d18e84d32e89bf0ec664b3c8f7b93. Change fails vaildation: rts/sm/Storage.c:1351:20: error: error: ‘gcc_clear_cache’ defined but not used [-Werror=unused-function] STATIC_INLINE void gcc_clear_cache(void * begin, void * end) >--------------------------------------------------------------- c6fe403ec714bf29cad9d94196f0db3c80a02235 rts/sm/Storage.c | 22 +--------------------- 1 file changed, 1 insertion(+), 21 deletions(-) diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c index 2e2834b..4aa4b12 100644 --- a/rts/sm/Storage.c +++ b/rts/sm/Storage.c @@ -1341,26 +1341,6 @@ StgWord calcTotalCompactW (void) #include #endif -#if defined(__GNUC__) -/* __clear_cache is a libgcc function. - * It existed before __builtin___clear_cache was introduced. - * See Trac #8562. - */ -extern void __clear_cache(char * begin, char * end); - -STATIC_INLINE void gcc_clear_cache(void * begin, void * end) -{ - /* __builtin___clear_cache is supported since GNU C 4.3.6. - * We pick 4.4 to simplify condition a bit. - */ -#if __GNUC__ > 4 || (__GNUC__ == 4 && __GNUC_MINOR__ >= 4) - __builtin___clear_cache(begin, end); -#else - __clear_cache(begin, end); -#endif -} -#endif /* __GNUC__ */ - /* On ARM and other platforms, we need to flush the cache after writing code into memory, so the processor reliably sees it. */ void flushExec (W_ len, AdjustorExecutable exec_addr) @@ -1376,7 +1356,7 @@ void flushExec (W_ len, AdjustorExecutable exec_addr) /* For all other platforms, fall back to a libgcc builtin. */ unsigned char* begin = (unsigned char*)exec_addr; unsigned char* end = begin + len; - gcc_clear_cache((void*)begin, (void*)end); + __clear_cache((void*)begin, (void*)end); #else #error Missing support to flush the instruction cache #endif From git at git.haskell.org Wed Jun 21 21:53:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Jun 2017 21:53:53 +0000 (UTC) Subject: [commit: ghc] master: rts: Suppress unused gcc_clear_cache warning (d1d3e98) Message-ID: <20170621215353.7C2603A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d1d3e98443cf263ef09253e2478e3e638e174e0d/ghc >--------------------------------------------------------------- commit d1d3e98443cf263ef09253e2478e3e638e174e0d Author: Ben Gamari Date: Wed Jun 21 16:57:07 2017 -0400 rts: Suppress unused gcc_clear_cache warning >--------------------------------------------------------------- d1d3e98443cf263ef09253e2478e3e638e174e0d rts/sm/Storage.c | 2 ++ 1 file changed, 2 insertions(+) diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c index 4aa4b12..ac4bf83 100644 --- a/rts/sm/Storage.c +++ b/rts/sm/Storage.c @@ -1345,6 +1345,8 @@ StgWord calcTotalCompactW (void) writing code into memory, so the processor reliably sees it. */ void flushExec (W_ len, AdjustorExecutable exec_addr) { + /* warning suppression */ + (void)gcc_clear_cache; #if defined(i386_HOST_ARCH) || defined(x86_64_HOST_ARCH) /* x86 doesn't need to do anything, so just suppress some warnings. */ (void)len; From git at git.haskell.org Wed Jun 21 21:57:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Jun 2017 21:57:14 +0000 (UTC) Subject: [commit: ghc] master: Revert "rts: Suppress unused gcc_clear_cache warning" (76769bd) Message-ID: <20170621215714.14CF93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/76769bdf9e423d89518eae4a5a441ae172c54e96/ghc >--------------------------------------------------------------- commit 76769bdf9e423d89518eae4a5a441ae172c54e96 Author: Ben Gamari Date: Wed Jun 21 17:56:59 2017 -0400 Revert "rts: Suppress unused gcc_clear_cache warning" This reverts commit d1d3e98443cf263ef09253e2478e3e638e174e0d. >--------------------------------------------------------------- 76769bdf9e423d89518eae4a5a441ae172c54e96 rts/sm/Storage.c | 2 -- 1 file changed, 2 deletions(-) diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c index ac4bf83..4aa4b12 100644 --- a/rts/sm/Storage.c +++ b/rts/sm/Storage.c @@ -1345,8 +1345,6 @@ StgWord calcTotalCompactW (void) writing code into memory, so the processor reliably sees it. */ void flushExec (W_ len, AdjustorExecutable exec_addr) { - /* warning suppression */ - (void)gcc_clear_cache; #if defined(i386_HOST_ARCH) || defined(x86_64_HOST_ARCH) /* x86 doesn't need to do anything, so just suppress some warnings. */ (void)len; From git at git.haskell.org Thu Jun 22 14:35:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jun 2017 14:35:17 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Add tcRnGetNameToInstancesIndex (9beb882) Message-ID: <20170622143517.9BD7A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/9beb882cab2b55fa070e86c1ba1dbc12732ad02c/ghc >--------------------------------------------------------------- commit 9beb882cab2b55fa070e86c1ba1dbc12732ad02c Author: Douglas Wilson Date: Thu Jun 8 15:02:01 2017 -0400 Add tcRnGetNameToInstancesIndex This function in tcRnDriver, retrieves an index by name of all Class and Family instances in the current environment. This is to be used by haddock which currently looks up instances for each name, which looks at every instance for every lookup. Using this function instead of tcRnGetInfo, the haddock.base performance test improves by 10% Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: alexbiehl, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3624 (cherry picked from commit 56ef54444b89b2332abe68ee62d88792f785f5a7) >--------------------------------------------------------------- 9beb882cab2b55fa070e86c1ba1dbc12732ad02c compiler/main/GHC.hs | 45 ++++++++++++++++++++++++++++++++++++++-- compiler/typecheck/TcRnDriver.hs | 1 + 2 files changed, 44 insertions(+), 2 deletions(-) diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index 0f7acbf..1dfa83e 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -1,4 +1,5 @@ -{-# LANGUAGE CPP, NondecreasingIndentation, ScopedTypeVariables #-} +{-# LANGUAGE CPP, NondecreasingIndentation, ScopedTypeVariables, + NamedFieldPuns, TupleSections #-} -- ----------------------------------------------------------------------------- -- @@ -113,6 +114,7 @@ module GHC ( getInfo, showModule, moduleIsBootOrNotObjectLinkable, + getNameToInstancesIndex, -- ** Inspecting types and kinds exprType, TcRnExprMode(..), @@ -333,8 +335,17 @@ import qualified Parser import Lexer import ApiAnnotation import qualified GHC.LanguageExtensions as LangExt +import NameEnv +import CoreFVs ( orphNamesOfFamInst ) +import FamInstEnv ( famInstEnvElts ) +import TcRnDriver +import Inst +import FamInst + +import Data.Foldable +import qualified Data.Map.Strict as Map import Data.Set (Set) - +import qualified Data.Sequence as Seq import System.Directory ( doesFileExist ) import Data.Maybe import Data.List ( find ) @@ -1227,6 +1238,36 @@ findGlobalAnns deserialize target = withSession $ \hsc_env -> do getGRE :: GhcMonad m => m GlobalRdrEnv getGRE = withSession $ \hsc_env-> return $ ic_rn_gbl_env (hsc_IC hsc_env) +-- | Retrieve all type and family instances in the environment, indexed +-- by 'Name'. Each name's lists will contain every instance in which that name +-- is mentioned in the instance head. +getNameToInstancesIndex :: HscEnv + -> IO (Messages, Maybe (NameEnv ([ClsInst], [FamInst]))) +getNameToInstancesIndex hsc_env + = runTcInteractive hsc_env $ + do { loadUnqualIfaces hsc_env (hsc_IC hsc_env) + ; InstEnvs {ie_global, ie_local, ie_visible} <- tcGetInstEnvs + ; (pkg_fie, home_fie) <- tcGetFamInstEnvs + -- We use flip mappend to maintain the order of instances, + -- and Data.Sequence.Seq to keep flip mappend fast + ; let cls_index = Map.fromListWith (flip mappend) + [ (n, Seq.singleton ispec) + | ispec <- instEnvElts ie_local ++ instEnvElts ie_global + , instIsVisible ie_visible ispec + , n <- nameSetElemsStable $ orphNamesOfClsInst ispec + ] + ; let fam_index = Map.fromListWith (flip mappend) + [ (n, Seq.singleton fispec) + | fispec <- famInstEnvElts home_fie ++ famInstEnvElts pkg_fie + , n <- nameSetElemsStable $ orphNamesOfFamInst fispec + ] + ; return $ mkNameEnv $ + [ (nm, (toList clss, toList fams)) + | (nm, (clss, fams)) <- Map.toList $ Map.unionWith mappend + (fmap (,Seq.empty) cls_index) + (fmap (Seq.empty,) fam_index) + ] } + -- ----------------------------------------------------------------------------- {- ToDo: Move the primary logic here to compiler/main/Packages.hs diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index ff3fcb9..740ed84 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -34,6 +34,7 @@ module TcRnDriver ( tcRnMergeSignatures, instantiateSignature, tcRnInstantiateSignature, + loadUnqualIfaces, -- More private... badReexportedBootThing, checkBootDeclM, From git at git.haskell.org Thu Jun 22 14:35:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jun 2017 14:35:25 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: base: Export Fingerprint accessors from Type.Reflection.Unsafe (9649420) Message-ID: <20170622143525.D00323A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/9649420a05e6417c05a46a3079b253bd69d03724/ghc >--------------------------------------------------------------- commit 9649420a05e6417c05a46a3079b253bd69d03724 Author: Ben Gamari Date: Tue Jun 20 14:59:40 2017 -0400 base: Export Fingerprint accessors from Type.Reflection.Unsafe Reviewers: dfeuer, austin, hvr Reviewed By: dfeuer Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3660 (cherry picked from commit 88263f93e0f3add38f925d5afb799eee8df32606) >--------------------------------------------------------------- 9649420a05e6417c05a46a3079b253bd69d03724 libraries/base/Type/Reflection/Unsafe.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/base/Type/Reflection/Unsafe.hs b/libraries/base/Type/Reflection/Unsafe.hs index 4cffd89..c0f2327 100644 --- a/libraries/base/Type/Reflection/Unsafe.hs +++ b/libraries/base/Type/Reflection/Unsafe.hs @@ -15,11 +15,11 @@ module Type.Reflection.Unsafe ( -- * Type representations - TypeRep, mkTrApp, mkTyCon + TypeRep, mkTrApp, mkTyCon, typeRepFingerprint, someTypeRepFingerprint -- * Kind representations , KindRep(..), TypeLitSort(..) -- * Type constructors - , TyCon, mkTrCon, tyConKindRep, tyConKindArgs, + , TyCon, mkTrCon, tyConKindRep, tyConKindArgs, tyConFingerprint ) where import Data.Typeable.Internal From git at git.haskell.org Thu Jun 22 14:35:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jun 2017 14:35:20 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Show only the number of modules in ghci (14ff644) Message-ID: <20170622143520.5F9743A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/14ff644c45e04ac6441f2faa3d2a518a7201ab11/ghc >--------------------------------------------------------------- commit 14ff644c45e04ac6441f2faa3d2a518a7201ab11 Author: Francesco Mazzoli Date: Tue Jun 20 15:00:20 2017 -0400 Show only the number of modules in ghci Reviewers: bgamari, austin, simonmar Reviewed By: bgamari Subscribers: mpickering, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3651 (cherry picked from commit c85cd9b2ff74c42f02a65edd74949267710f02f4) >--------------------------------------------------------------- 14ff644c45e04ac6441f2faa3d2a518a7201ab11 ghc/GHCi/UI.hs | 27 +++++++++------------------ testsuite/tests/driver/T8526/T8526.stdout | 4 ++-- testsuite/tests/ghci/scripts/T1914.stdout | 6 +++--- testsuite/tests/ghci/scripts/T6105.stdout | 4 ++-- testsuite/tests/ghci/scripts/ghci058.stdout | 4 ++-- 5 files changed, 18 insertions(+), 27 deletions(-) diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs index a509f28..9173d75 100644 --- a/ghc/GHCi/UI.hs +++ b/ghc/GHCi/UI.hs @@ -51,7 +51,7 @@ import GHC ( LoadHowMuch(..), Target(..), TargetId(..), InteractiveImport(..), import HsImpExp import HsSyn import HscTypes ( tyThingParent_maybe, handleFlagWarnings, getSafeMode, hsc_IC, - setInteractivePrintName, hsc_dflags, msObjFilePath ) + setInteractivePrintName, hsc_dflags ) import Module import Name import Packages ( trusted, getPackageDetails, getInstalledPackageDetails, @@ -1721,7 +1721,7 @@ afterLoad ok retain_context = do lift revertCAFs -- always revert CAFs on load. lift discardTickArrays loaded_mods <- getLoadedModules - modulesLoadedMsg ok loaded_mods + modulesLoadedMsg ok (length loaded_mods) lift $ setContextAfterLoad retain_context loaded_mods setContextAfterLoad :: Bool -> [GHC.ModSummary] -> GHCi () @@ -1796,27 +1796,18 @@ keepPackageImports = filterM is_pkg_import mod_name = unLoc (ideclName d) -modulesLoadedMsg :: SuccessFlag -> [GHC.ModSummary] -> InputT GHCi () -modulesLoadedMsg ok mods = do +modulesLoadedMsg :: SuccessFlag -> Int -> InputT GHCi () +modulesLoadedMsg ok num_mods = do dflags <- getDynFlags unqual <- GHC.getPrintUnqual - let mod_name mod = do - is_interpreted <- GHC.moduleIsBootOrNotObjectLinkable mod - return $ if is_interpreted - then ppr (GHC.ms_mod mod) - else ppr (GHC.ms_mod mod) - <> text " (" - <> text (normalise $ msObjFilePath mod) - <> text ")" -- fix #9887 - mod_names <- mapM mod_name mods - let mod_commas - | null mods = text "none." - | otherwise = hsep (punctuate comma mod_names) <> text "." - status = case ok of + let status = case ok of Failed -> text "Failed" Succeeded -> text "Ok" - msg = status <> text ", modules loaded:" <+> mod_commas + num_mods_pp = if num_mods == 1 + then "1 module" + else int num_mods <+> "modules" + msg = status <> text "," <+> num_mods_pp <+> "loaded." when (verbosity dflags > 0) $ liftIO $ putStrLn $ showSDocForUser dflags unqual msg diff --git a/testsuite/tests/driver/T8526/T8526.stdout b/testsuite/tests/driver/T8526/T8526.stdout index 3b24506..83b8f95 100644 --- a/testsuite/tests/driver/T8526/T8526.stdout +++ b/testsuite/tests/driver/T8526/T8526.stdout @@ -1,6 +1,6 @@ [1 of 1] Compiling A ( A.hs, interpreted ) -Ok, modules loaded: A. +Ok, 1 module loaded. True [1 of 1] Compiling A ( A.hs, interpreted ) -Ok, modules loaded: A. +Ok, 1 module loaded. False diff --git a/testsuite/tests/ghci/scripts/T1914.stdout b/testsuite/tests/ghci/scripts/T1914.stdout index 063758e..2d1a82b 100644 --- a/testsuite/tests/ghci/scripts/T1914.stdout +++ b/testsuite/tests/ghci/scripts/T1914.stdout @@ -1,7 +1,7 @@ [1 of 2] Compiling T1914B ( T1914B.hs, interpreted ) [2 of 2] Compiling T1914A ( T1914A.hs, interpreted ) -Ok, modules loaded: T1914A, T1914B. +Ok, 2 modules loaded. [2 of 2] Compiling T1914A ( T1914A.hs, interpreted ) -Failed, modules loaded: T1914B. +Failed, 1 module loaded. [2 of 2] Compiling T1914A ( T1914A.hs, interpreted ) -Ok, modules loaded: T1914A, T1914B. +Ok, 2 modules loaded. diff --git a/testsuite/tests/ghci/scripts/T6105.stdout b/testsuite/tests/ghci/scripts/T6105.stdout index 73b6d2c..6a846e3 100644 --- a/testsuite/tests/ghci/scripts/T6105.stdout +++ b/testsuite/tests/ghci/scripts/T6105.stdout @@ -1,4 +1,4 @@ [1 of 1] Compiling T6105 ( T6105.hs, interpreted ) -Ok, modules loaded: T6105. +Ok, 1 module loaded. [1 of 1] Compiling T6105 ( T6105.hs, interpreted ) -Ok, modules loaded: T6105. +Ok, 1 module loaded. diff --git a/testsuite/tests/ghci/scripts/ghci058.stdout b/testsuite/tests/ghci/scripts/ghci058.stdout index bc77f05..2028aee 100644 --- a/testsuite/tests/ghci/scripts/ghci058.stdout +++ b/testsuite/tests/ghci/scripts/ghci058.stdout @@ -1,4 +1,4 @@ -Ok, modules loaded: Ghci058 (Ghci058.o). +Ok, 1 module loaded. 'a' -Ok, modules loaded: Ghci058 (Ghci058.o). +Ok, 1 module loaded. 'b' From git at git.haskell.org Thu Jun 22 14:35:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jun 2017 14:35:23 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Improve getNameToInstancesIndex (4f4f05a) Message-ID: <20170622143523.1FE673A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/4f4f05a6baf2f9616f8a48357d417a6855ff940e/ghc >--------------------------------------------------------------- commit 4f4f05a6baf2f9616f8a48357d417a6855ff940e Author: Douglas Wilson Date: Mon Jun 12 17:02:01 2017 -0400 Improve getNameToInstancesIndex Put it in a GhcMonad. Stop accidentally reversing the list of instances. Add a comment noting the code is mostly copied from tcRnGetInfo. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: mpickering, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3636 (cherry picked from commit f942f65a525dd972cd96e6ae42922b6a3ce4b2d0) >--------------------------------------------------------------- 4f4f05a6baf2f9616f8a48357d417a6855ff940e compiler/main/GHC.hs | 18 ++++++++++-------- compiler/typecheck/TcRnDriver.hs | 8 ++++++++ 2 files changed, 18 insertions(+), 8 deletions(-) diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index 1dfa83e..8f50841 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -1241,22 +1241,24 @@ getGRE = withSession $ \hsc_env-> return $ ic_rn_gbl_env (hsc_IC hsc_env) -- | Retrieve all type and family instances in the environment, indexed -- by 'Name'. Each name's lists will contain every instance in which that name -- is mentioned in the instance head. -getNameToInstancesIndex :: HscEnv - -> IO (Messages, Maybe (NameEnv ([ClsInst], [FamInst]))) -getNameToInstancesIndex hsc_env - = runTcInteractive hsc_env $ +getNameToInstancesIndex :: GhcMonad m + => m (Messages, Maybe (NameEnv ([ClsInst], [FamInst]))) +getNameToInstancesIndex = do + hsc_env <- getSession + liftIO $ runTcInteractive hsc_env $ do { loadUnqualIfaces hsc_env (hsc_IC hsc_env) ; InstEnvs {ie_global, ie_local, ie_visible} <- tcGetInstEnvs ; (pkg_fie, home_fie) <- tcGetFamInstEnvs - -- We use flip mappend to maintain the order of instances, - -- and Data.Sequence.Seq to keep flip mappend fast - ; let cls_index = Map.fromListWith (flip mappend) + -- We use Data.Sequence.Seq because we are creating left associated + -- mappends. + -- cls_index and fam_index below are adapted from TcRnDriver.lookupInsts + ; let cls_index = Map.fromListWith mappend [ (n, Seq.singleton ispec) | ispec <- instEnvElts ie_local ++ instEnvElts ie_global , instIsVisible ie_visible ispec , n <- nameSetElemsStable $ orphNamesOfClsInst ispec ] - ; let fam_index = Map.fromListWith (flip mappend) + ; let fam_index = Map.fromListWith mappend [ (n, Seq.singleton fispec) | fispec <- famInstEnvElts home_fie ++ famInstEnvElts pkg_fie , n <- nameSetElemsStable $ orphNamesOfFamInst fispec diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index 740ed84..1f7a5e6 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -2436,6 +2436,14 @@ tcRnGetInfo hsc_env name ; (cls_insts, fam_insts) <- lookupInsts thing ; return (thing, fixity, cls_insts, fam_insts) } + +-- Lookup all class and family instances for a type constructor. +-- +-- This function filters all instances in the type environment, so there +-- is a lot of duplicated work if it is called many times in the same +-- type environment. If this becomes a problem, the NameEnv computed +-- in GHC.getNameToInstancesIndex could be cached in TcM and both functions +-- could be changed to consult that index. lookupInsts :: TyThing -> TcM ([ClsInst],[FamInst]) lookupInsts (ATyCon tc) = do { InstEnvs { ie_global = pkg_ie, ie_local = home_ie, ie_visible = vis_mods } <- tcGetInstEnvs From git at git.haskell.org Thu Jun 22 15:00:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jun 2017 15:00:21 +0000 (UTC) Subject: [commit: ghc] master: Fix typo (a9bf7d4) Message-ID: <20170622150021.49F683A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a9bf7d42bb31d66e8669546e47191961bc03da03/ghc >--------------------------------------------------------------- commit a9bf7d42bb31d66e8669546e47191961bc03da03 Author: 5outh Date: Thu Jun 22 10:29:53 2017 -0400 Fix typo >--------------------------------------------------------------- a9bf7d42bb31d66e8669546e47191961bc03da03 libraries/base/GHC/Conc/Sync.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/GHC/Conc/Sync.hs b/libraries/base/GHC/Conc/Sync.hs index 44d34d8..f9514d6 100644 --- a/libraries/base/GHC/Conc/Sync.hs +++ b/libraries/base/GHC/Conc/Sync.hs @@ -731,7 +731,7 @@ atomically (STM m) = IO (\s -> (atomically# m) s ) -- values in TVars which mean that it should not continue (e.g. the TVars -- represent a shared buffer that is now empty). The implementation may -- block the thread until one of the TVars that it has read from has been --- udpated. (GHC only) +-- updated. (GHC only) retry :: STM a retry = STM $ \s# -> retry# s# From git at git.haskell.org Thu Jun 22 18:43:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jun 2017 18:43:31 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump Haddock submodule (2ce8641) Message-ID: <20170622184331.F0BF33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/2ce8641a1668c9d7a249351c427644107258d49d/ghc >--------------------------------------------------------------- commit 2ce8641a1668c9d7a249351c427644107258d49d Author: Ben Gamari Date: Thu Jun 22 14:42:14 2017 -0400 Bump Haddock submodule >--------------------------------------------------------------- 2ce8641a1668c9d7a249351c427644107258d49d utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 87c551f..d5d8cd1 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 87c551fc668b9251f2647cce8772f205e1cee154 +Subproject commit d5d8cd1722b06f17155e830f2242a073b0a983eb From git at git.haskell.org Thu Jun 22 21:36:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jun 2017 21:36:01 +0000 (UTC) Subject: [commit: ghc] master: UNREG: use __builtin___clear_cache where available (34b7f63) Message-ID: <20170622213601.CB2EA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/34b7f63e285e6152875e75f677ad8f8e9ead5963/ghc >--------------------------------------------------------------- commit 34b7f63e285e6152875e75f677ad8f8e9ead5963 Author: Sergei Trofimovich Date: Wed Jun 21 21:17:51 2017 +0100 UNREG: use __builtin___clear_cache where available Noticed when was building UNREG ghc with -optc{-Wall,-Werror}: rts/sm/Storage.c:1359:3: error: error: implicit declaration of function '__clear_cache' [-Werror=implicit-function-declaration] __clear_cache((void*)begin, (void*)end); ^~~~~~~~~~~~~ | 1359 | __clear_cache((void*)begin, (void*)end); | ^ Left direct '__clear_cache' usage gcc toolchain before 4.4. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 34b7f63e285e6152875e75f677ad8f8e9ead5963 rts/sm/Storage.c | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c index 4aa4b12..e243517 100644 --- a/rts/sm/Storage.c +++ b/rts/sm/Storage.c @@ -1341,6 +1341,14 @@ StgWord calcTotalCompactW (void) #include #endif +#if defined(__GNUC__) +/* __clear_cache is a libgcc function. + * It existed before __builtin___clear_cache was introduced. + * See Trac #8562. + */ +extern void __clear_cache(char * begin, char * end); +#endif /* __GNUC__ */ + /* On ARM and other platforms, we need to flush the cache after writing code into memory, so the processor reliably sees it. */ void flushExec (W_ len, AdjustorExecutable exec_addr) @@ -1356,7 +1364,15 @@ void flushExec (W_ len, AdjustorExecutable exec_addr) /* 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. + */ +# if __GNUC__ > 4 || (__GNUC__ == 4 && __GNUC_MINOR__ >= 4) + __builtin___clear_cache((void*)begin, (void*)end); +# else __clear_cache((void*)begin, (void*)end); +# endif #else #error Missing support to flush the instruction cache #endif From git at git.haskell.org Fri Jun 23 17:07:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jun 2017 17:07:53 +0000 (UTC) Subject: [commit: ghc] master: compiler: Eliminate pprTrace in SPT entry addition codepath (84cf095) Message-ID: <20170623170753.D038E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/84cf095dc981ea21fcceddbb71463dd7844754ca/ghc >--------------------------------------------------------------- commit 84cf095dc981ea21fcceddbb71463dd7844754ca Author: Ben Gamari Date: Fri Jun 23 11:35:48 2017 -0400 compiler: Eliminate pprTrace in SPT entry addition codepath Test Plan: Load program with StaticPointers into GHCi, ensure no tracing output makes it in. Reviewers: austin Subscribers: rwbarton, thomie, RyanGlScott GHC Trac Issues: #12356 Differential Revision: https://phabricator.haskell.org/D3663 >--------------------------------------------------------------- 84cf095dc981ea21fcceddbb71463dd7844754ca compiler/main/HscMain.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index d2b6e5b..b8bd76b 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -1611,8 +1611,7 @@ hscAddSptEntries hsc_env entries = do let add_spt_entry :: SptEntry -> IO () add_spt_entry (SptEntry i fpr) = do val <- getHValue hsc_env (idName i) - pprTrace "add_spt_entry" (ppr fpr <+> ppr i) $ - addSptEntry hsc_env fpr val + addSptEntry hsc_env fpr val mapM_ add_spt_entry entries {- From git at git.haskell.org Fri Jun 23 17:07:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jun 2017 17:07:56 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Fix cabal01 test (e13edee) Message-ID: <20170623170756.860163A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e13edee31780704e521f764485a372766dd54daa/ghc >--------------------------------------------------------------- commit e13edee31780704e521f764485a372766dd54daa Author: Ben Gamari Date: Fri Jun 23 11:36:38 2017 -0400 testsuite: Fix cabal01 test The other-modules field listed things that weren't in fact modules, causing this test to fail. See Cabal #4567. Test Plan: Validate Reviewers: hvr, austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3665 >--------------------------------------------------------------- e13edee31780704e521f764485a372766dd54daa testsuite/tests/cabal/cabal01/test.cabal | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/cabal/cabal01/test.cabal b/testsuite/tests/cabal/cabal01/test.cabal index f49d874..fe66d70 100644 --- a/testsuite/tests/cabal/cabal01/test.cabal +++ b/testsuite/tests/cabal/cabal01/test.cabal @@ -7,10 +7,10 @@ Extensions: ForeignFunctionInterface Build-depends: base>=1.0 Executable: testA -Other-Modules: A, MainA +Other-Modules: A Main-is: MainA.hs Extensions: OverlappingInstances Executable: testB -Other-Modules: B.A, B.MainB +Other-Modules: B.A Main-is: B/MainB.hs From git at git.haskell.org Fri Jun 23 17:07:59 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jun 2017 17:07:59 +0000 (UTC) Subject: [commit: ghc] master: Add fixity declaration for Data.List.NonEmpty.!! (398a444) Message-ID: <20170623170759.404E03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/398a444bc673aa4bbdd30029e2cce440f0309e34/ghc >--------------------------------------------------------------- commit 398a444bc673aa4bbdd30029e2cce440f0309e34 Author: Ryan Scott Date: Fri Jun 23 11:37:19 2017 -0400 Add fixity declaration for Data.List.NonEmpty.!! We have `infixl 9 !!` for `Data.List.!!`, but not for `Data.List.NonEmpty.!!`. We ought to. Test Plan: Read it Reviewers: bgamari, austin, hvr Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3666 >--------------------------------------------------------------- 398a444bc673aa4bbdd30029e2cce440f0309e34 libraries/base/Data/List/NonEmpty.hs | 1 + libraries/base/changelog.md | 1 + 2 files changed, 2 insertions(+) diff --git a/libraries/base/Data/List/NonEmpty.hs b/libraries/base/Data/List/NonEmpty.hs index 9a9de01..d1cc28c 100644 --- a/libraries/base/Data/List/NonEmpty.hs +++ b/libraries/base/Data/List/NonEmpty.hs @@ -477,6 +477,7 @@ isPrefixOf (y:ys) (x :| xs) = (y == x) && List.isPrefixOf ys xs | n == 0 = x | n > 0 = xs List.!! (n - 1) | otherwise = errorWithoutStackTrace "NonEmpty.!! negative argument" +infixl 9 !! -- | The 'zip' function takes two streams and returns a stream of -- corresponding pairs. diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 69baab3..0cfd9c1 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -8,6 +8,7 @@ * Add instances `Num`, `Functor`, `Applicative`, `Monad`, `Semigroup` and `Monoid` for `Data.Ord.Down` (#13097). + * Add `infixl 9 !!` declaration for `Data.List.NonEmpty.!!` ## 4.10.0.0 *April 2017* * Bundled with GHC *TBA* From git at git.haskell.org Fri Jun 23 17:08:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jun 2017 17:08:05 +0000 (UTC) Subject: [commit: ghc] master: Use actual universal tvs in check for naughty record selectors (9077120) Message-ID: <20170623170805.533833A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9077120918b78f5152bf3596fe6df07b91cead79/ghc >--------------------------------------------------------------- commit 9077120918b78f5152bf3596fe6df07b91cead79 Author: Matthew Pickering Date: Fri Jun 23 11:40:50 2017 -0400 Use actual universal tvs in check for naughty record selectors The naughty record selector check means to limit selectors which would lead to existential tyvars escaping their scope. With record pattern synonyms, there are situations where universal tyvars don't appear in the result type, for example: ``` pattern ReadP :: Read a => a -> String pattern ReadP{readp} <- (read -> readp) ``` This is a similar issue to #11224 where we assumed that we can decide which variables are universal and which are existential by the syntactic check of seeing which appear in the result type. The fix is to use `univ_tvs` from `conLikeFullSig` rather than the previous approximation. But we must also remember to apply `EqSpec`s so we use the free variables from `inst_tys` which is precisely `univ_tvs` with `EqSpecs` applied. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3649 >--------------------------------------------------------------- 9077120918b78f5152bf3596fe6df07b91cead79 compiler/typecheck/TcTyDecls.hs | 2 +- testsuite/tests/patsyn/should_run/records-run.hs | 7 +++++++ testsuite/tests/patsyn/should_run/records-run.stdout | 1 + 3 files changed, 9 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcTyDecls.hs b/compiler/typecheck/TcTyDecls.hs index df33bb0..68e15fb 100644 --- a/compiler/typecheck/TcTyDecls.hs +++ b/compiler/typecheck/TcTyDecls.hs @@ -846,7 +846,7 @@ mkOneRecordSelector all_cons idDetails fl -- Selector type; Note [Polymorphic selectors] field_ty = conLikeFieldType con1 lbl - data_tvs = tyCoVarsOfTypeWellScoped data_ty + data_tvs = tyCoVarsOfTypesWellScoped inst_tys data_tv_set= mkVarSet data_tvs is_naughty = not (tyCoVarsOfType field_ty `subVarSet` data_tv_set) (field_tvs, field_theta, field_tau) = tcSplitSigmaTy field_ty diff --git a/testsuite/tests/patsyn/should_run/records-run.hs b/testsuite/tests/patsyn/should_run/records-run.hs index 19a6bb2..1719045 100644 --- a/testsuite/tests/patsyn/should_run/records-run.hs +++ b/testsuite/tests/patsyn/should_run/records-run.hs @@ -1,4 +1,6 @@ {-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE ViewPatterns #-} module Main where @@ -6,9 +8,14 @@ pattern Bi{a, b} = (a, b) foo = ("a","b") +pattern ReadP :: Read a => a -> String +pattern ReadP {readp} <- (read -> readp) + main = do print foo print (a foo) print (b foo) print (foo {a = "c"}) print (foo {a = "fst", b = "snd"}) + + print (readp @Int "5") diff --git a/testsuite/tests/patsyn/should_run/records-run.stdout b/testsuite/tests/patsyn/should_run/records-run.stdout index a0878c7..e76be9c 100644 --- a/testsuite/tests/patsyn/should_run/records-run.stdout +++ b/testsuite/tests/patsyn/should_run/records-run.stdout @@ -3,3 +3,4 @@ "b" ("c","b") ("fst","snd") +5 From git at git.haskell.org Fri Jun 23 17:08:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jun 2017 17:08:02 +0000 (UTC) Subject: [commit: ghc] master: Fix pretty-printing of zero-argument lambda expressions (3c4537e) Message-ID: <20170623170802.96A6A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3c4537ea1c940966eddcb9cb418bf8e39b8f0f1c/ghc >--------------------------------------------------------------- commit 3c4537ea1c940966eddcb9cb418bf8e39b8f0f1c Author: Ryan Scott Date: Fri Jun 23 11:40:10 2017 -0400 Fix pretty-printing of zero-argument lambda expressions Using Template Haskell, one can construct lambda expressions with no arguments. The pretty-printer isn't aware of this fact, however. This changes that. Test Plan: make test TEST=T13856 Reviewers: bgamari, austin, goldfire Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13856 Differential Revision: https://phabricator.haskell.org/D3664 >--------------------------------------------------------------- 3c4537ea1c940966eddcb9cb418bf8e39b8f0f1c compiler/hsSyn/Convert.hs | 4 ++++ libraries/template-haskell/Language/Haskell/TH/Ppr.hs | 1 + testsuite/tests/th/T13856.hs | 8 ++++++++ testsuite/tests/th/T13856.stderr | 1 + testsuite/tests/th/all.T | 1 + 5 files changed, 15 insertions(+) diff --git a/compiler/hsSyn/Convert.hs b/compiler/hsSyn/Convert.hs index 5ded8bc..8b7af27 100644 --- a/compiler/hsSyn/Convert.hs +++ b/compiler/hsSyn/Convert.hs @@ -784,6 +784,10 @@ cvtl e = wrapL (cvt e) ; t' <- cvtType t ; tp <- wrap_apps t' ; return $ HsAppType e' $ mkHsWildCardBndrs tp } + cvt (LamE [] e) = cvt e -- Degenerate case. We convert the body as its + -- own expression to avoid pretty-printing + -- oddities that can result from zero-argument + -- lambda expressions. See #13856. cvt (LamE ps e) = do { ps' <- cvtPats ps; e' <- cvtl e ; return $ HsLam (mkMatchGroup FromSource [mkSimpleMatch LambdaExpr ps' e'])} diff --git a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs index a851a22..4173991 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs @@ -143,6 +143,7 @@ pprExp i (InfixE (Just e1) op (Just e2)) pprExp _ (InfixE me1 op me2) = parens $ pprMaybeExp noPrec me1 <+> pprInfixExp op <+> pprMaybeExp noPrec me2 +pprExp i (LamE [] e) = pprExp i e -- #13856 pprExp i (LamE ps e) = parensIf (i > noPrec) $ char '\\' <> hsep (map (pprPat appPrec) ps) <+> text "->" <+> ppr e pprExp i (LamCaseE ms) = parensIf (i > noPrec) diff --git a/testsuite/tests/th/T13856.hs b/testsuite/tests/th/T13856.hs new file mode 100644 index 0000000..d1ef71d --- /dev/null +++ b/testsuite/tests/th/T13856.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# OPTIONS_GHC -ddump-splices #-} +module T13856 where + +import Language.Haskell.TH + +f :: Int +f = $(lamE [] [| 42 |]) diff --git a/testsuite/tests/th/T13856.stderr b/testsuite/tests/th/T13856.stderr new file mode 100644 index 0000000..141b7a2 --- /dev/null +++ b/testsuite/tests/th/T13856.stderr @@ -0,0 +1 @@ +T13856.hs:8:7-22: Splicing expression lamE [] [| 42 |] ======> 42 diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 1f0a7ec..0092e5a 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -388,3 +388,4 @@ test('T13618', normal, compile_and_run, ['-v0']) test('T13642', normal, compile_fail, ['-v0']) test('T13781', normal, compile, ['-v0']) test('T13782', normal, compile, ['']) +test('T13856', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques']) From git at git.haskell.org Fri Jun 23 17:08:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jun 2017 17:08:09 +0000 (UTC) Subject: [commit: ghc] master: Hoopl: remove dependency on Hoopl package (42eee6e) Message-ID: <20170623170809.0C0A03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/42eee6eac3d4bf4b2b557cdc13f2d5acae93d4e8/ghc >--------------------------------------------------------------- commit 42eee6eac3d4bf4b2b557cdc13f2d5acae93d4e8 Author: Michal Terepeta Date: Fri Jun 23 11:41:50 2017 -0400 Hoopl: remove dependency on Hoopl package This copies the subset of Hoopl's functionality needed by GHC to `cmm/Hoopl` and removes the dependency on the Hoopl package. The main motivation for this change is the confusing/noisy interface between GHC and Hoopl: - Hoopl has `Label` which is GHC's `BlockId` but different than GHC's `CLabel` - Hoopl has `Unique` which is different than GHC's `Unique` - Hoopl has `Unique{Map,Set}` which are different than GHC's `Uniq{FM,Set}` - GHC has its own specialized copy of `Dataflow`, so `cmm/Hoopl` is needed just to filter the exposed functions (filter out some of the Hoopl's and add the GHC ones) With this change, we'll be able to simplify this significantly. It'll also be much easier to do invasive changes (Hoopl is a public package on Hackage with users that depend on the current behavior) This should introduce no changes in functionality - it merely copies the relevant code. Signed-off-by: Michal Terepeta Test Plan: ./validate Reviewers: austin, bgamari, simonmar Reviewed By: bgamari, simonmar Subscribers: simonpj, kavon, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3616 >--------------------------------------------------------------- 42eee6eac3d4bf4b2b557cdc13f2d5acae93d4e8 compiler/cmm/BlockId.hs | 13 +- compiler/cmm/Cmm.hs | 5 +- compiler/cmm/CmmBuildInfoTables.hs | 6 +- compiler/cmm/CmmCommonBlockElim.hs | 5 +- compiler/cmm/CmmContFlowOpt.hs | 5 +- compiler/cmm/CmmImplementSwitchPlans.hs | 2 +- compiler/cmm/CmmInfo.hs | 2 +- compiler/cmm/CmmLayoutStack.hs | 6 +- compiler/cmm/CmmLint.hs | 5 +- compiler/cmm/CmmLive.hs | 5 +- compiler/cmm/CmmNode.hs | 4 +- compiler/cmm/CmmPipeline.hs | 2 +- compiler/cmm/CmmProcPoint.hs | 6 +- compiler/cmm/CmmSink.hs | 5 +- compiler/cmm/CmmSwitch.hs | 2 +- compiler/cmm/CmmUtils.hs | 5 +- compiler/cmm/Debug.hs | 5 +- compiler/cmm/Hoopl.hs | 29 -- compiler/cmm/Hoopl/Block.hs | 327 +++++++++++++++++++++ compiler/cmm/Hoopl/Collections.hs | 87 ++++++ compiler/cmm/Hoopl/Dataflow.hs | 12 +- compiler/cmm/Hoopl/Graph.hs | 199 +++++++++++++ compiler/cmm/Hoopl/Label.hs | 122 ++++++++ compiler/cmm/Hoopl/Unique.hs | 91 ++++++ compiler/cmm/MkGraph.hs | 4 +- compiler/cmm/PprC.hs | 4 +- compiler/cmm/PprCmm.hs | 3 +- compiler/codeGen/CgUtils.hs | 3 +- compiler/codeGen/StgCmmHeap.hs | 2 +- compiler/codeGen/StgCmmMonad.hs | 2 +- compiler/ghc.cabal.in | 9 +- compiler/llvmGen/LlvmCodeGen.hs | 3 +- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 4 +- compiler/nativeGen/AsmCodeGen.hs | 4 +- compiler/nativeGen/Dwarf.hs | 3 +- compiler/nativeGen/Instruction.hs | 3 +- compiler/nativeGen/NCGMonad.hs | 5 +- compiler/nativeGen/PIC.hs | 2 +- compiler/nativeGen/PPC/CodeGen.hs | 3 +- compiler/nativeGen/PPC/Instr.hs | 3 +- compiler/nativeGen/PPC/Ppr.hs | 3 +- compiler/nativeGen/RegAlloc/Graph/Spill.hs | 2 +- compiler/nativeGen/RegAlloc/Graph/SpillClean.hs | 2 +- compiler/nativeGen/RegAlloc/Graph/SpillCost.hs | 2 +- .../nativeGen/RegAlloc/Linear/JoinToTargets.hs | 2 +- compiler/nativeGen/RegAlloc/Linear/Main.hs | 2 +- compiler/nativeGen/RegAlloc/Liveness.hs | 3 +- compiler/nativeGen/SPARC/CodeGen.hs | 3 +- compiler/nativeGen/SPARC/Ppr.hs | 3 +- compiler/nativeGen/X86/CodeGen.hs | 3 +- compiler/nativeGen/X86/Instr.hs | 3 +- compiler/nativeGen/X86/Ppr.hs | 3 +- ghc.mk | 3 +- libraries/hoopl | 1 - packages | 1 - 55 files changed, 948 insertions(+), 95 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 42eee6eac3d4bf4b2b557cdc13f2d5acae93d4e8 From git at git.haskell.org Fri Jun 23 18:51:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jun 2017 18:51:52 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: change filtering of variables in extract_hs_tv_bndrs (fixes #13782) (05ae09c) Message-ID: <20170623185152.1D9F13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/05ae09c7fac3e82a0b651980080fc472eb15e995/ghc >--------------------------------------------------------------- commit 05ae09c7fac3e82a0b651980080fc472eb15e995 Author: Carlos Tomé Date: Tue Jun 20 15:00:46 2017 -0400 change filtering of variables in extract_hs_tv_bndrs (fixes #13782) Reviewers: austin, bgamari, goldfire Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13782 Differential Revision: https://phabricator.haskell.org/D3641 (cherry picked from commit c8370a821bb92ca3846953cb0b37250720087135) >--------------------------------------------------------------- 05ae09c7fac3e82a0b651980080fc472eb15e995 compiler/rename/RnTypes.hs | 107 +++++++++++-------------------------------- testsuite/tests/th/T13782.hs | 14 ++++++ testsuite/tests/th/all.T | 1 + 3 files changed, 43 insertions(+), 79 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 05ae09c7fac3e82a0b651980080fc472eb15e995 From git at git.haskell.org Fri Jun 23 18:51:54 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jun 2017 18:51:54 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Add missing -Wdeprecations flag to the users guide (9057c25) Message-ID: <20170623185154.D01D43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/9057c250e3030a25a6ac3d736a7657ae78889897/ghc >--------------------------------------------------------------- commit 9057c250e3030a25a6ac3d736a7657ae78889897 Author: erdeszt Date: Sat Jun 17 13:47:10 2017 +0200 Add missing -Wdeprecations flag to the users guide (cherry picked from commit 986deaa5539552f84b4f1d1872ae8a4c8240097e) >--------------------------------------------------------------- 9057c250e3030a25a6ac3d736a7657ae78889897 docs/users_guide/using-warnings.rst | 13 +++++++++++++ utils/mkUserGuidePart/Options/Warnings.hs | 7 +++++++ 2 files changed, 20 insertions(+) diff --git a/docs/users_guide/using-warnings.rst b/docs/users_guide/using-warnings.rst index ed2b12b..67c7ae4 100644 --- a/docs/users_guide/using-warnings.rst +++ b/docs/users_guide/using-warnings.rst @@ -17,6 +17,7 @@ generally likely to indicate bugs in your program. These are: * :ghc-flag:`-Woverlapping-patterns` * :ghc-flag:`-Wwarnings-deprecations` + * :ghc-flag:`-Wdeprecations` * :ghc-flag:`-Wdeprecated-flags` * :ghc-flag:`-Wunrecognised-pragmas` * :ghc-flag:`-Wduplicate-constraints` @@ -246,6 +247,18 @@ of ``-W(no-)*``. This option is on by default. +.. ghc-flag:: -Wdeprecations + + .. index:: + single: deprecations + + Causes a warning to be emitted when a module, function or type with + a ``WARNING`` or ``DEPRECATED pragma`` is used. See + :ref:`warning-deprecated-pragma` for more details on the pragmas. + An alias for :ghc-flag:`-Wwarnings-deprecations`. + + This option is on by default. + .. ghc-flag:: -Wamp .. index:: diff --git a/utils/mkUserGuidePart/Options/Warnings.hs b/utils/mkUserGuidePart/Options/Warnings.hs index 48ee32c..620c731 100644 --- a/utils/mkUserGuidePart/Options/Warnings.hs +++ b/utils/mkUserGuidePart/Options/Warnings.hs @@ -401,6 +401,13 @@ warningsOptions = , flagType = DynamicFlag , flagReverse = "-Wno-warnings-deprecations" } + , flag { flagName = "-Wdeprecations" + , flagDescription = + "warn about uses of functions & types that have warnings or "++ + "deprecated pragmas. Alias for :ghc-flag:`-Wwarnings-deprecations`" + , flagType = DynamicFlag + , flagReverse = "-Wno-deprecations" + } , flag { flagName = "-Wamp" , flagDescription = "*(deprecated)* warn on definitions conflicting with the "++ From git at git.haskell.org Fri Jun 23 18:51:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jun 2017 18:51:57 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: compiler: Eliminate pprTrace in SPT entry addition codepath (0fa0d6c) Message-ID: <20170623185157.86C3B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/0fa0d6c2d64dc41783e04b5887f96a996a181d3b/ghc >--------------------------------------------------------------- commit 0fa0d6c2d64dc41783e04b5887f96a996a181d3b Author: Ben Gamari Date: Fri Jun 23 11:35:48 2017 -0400 compiler: Eliminate pprTrace in SPT entry addition codepath Test Plan: Load program with StaticPointers into GHCi, ensure no tracing output makes it in. Reviewers: austin Subscribers: rwbarton, thomie, RyanGlScott GHC Trac Issues: #12356 Differential Revision: https://phabricator.haskell.org/D3663 (cherry picked from commit 84cf095dc981ea21fcceddbb71463dd7844754ca) >--------------------------------------------------------------- 0fa0d6c2d64dc41783e04b5887f96a996a181d3b compiler/main/HscMain.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index fd8c2c0..43dc5a1 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -1613,8 +1613,7 @@ hscAddSptEntries hsc_env entries = do let add_spt_entry :: SptEntry -> IO () add_spt_entry (SptEntry i fpr) = do val <- getHValue hsc_env (idName i) - pprTrace "add_spt_entry" (ppr fpr <+> ppr i) $ - addSptEntry hsc_env fpr val + addSptEntry hsc_env fpr val mapM_ add_spt_entry entries {- From git at git.haskell.org Fri Jun 23 18:52:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jun 2017 18:52:00 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: testsuite: Fix cabal01 test (379c07b) Message-ID: <20170623185200.3BB443A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/379c07bb69d0ad0249466737bcd3efd50f3bd966/ghc >--------------------------------------------------------------- commit 379c07bb69d0ad0249466737bcd3efd50f3bd966 Author: Ben Gamari Date: Fri Jun 23 11:36:38 2017 -0400 testsuite: Fix cabal01 test The other-modules field listed things that weren't in fact modules, causing this test to fail. See Cabal #4567. Test Plan: Validate Reviewers: hvr, austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3665 (cherry picked from commit e13edee31780704e521f764485a372766dd54daa) >--------------------------------------------------------------- 379c07bb69d0ad0249466737bcd3efd50f3bd966 testsuite/tests/cabal/cabal01/test.cabal | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/cabal/cabal01/test.cabal b/testsuite/tests/cabal/cabal01/test.cabal index f49d874..fe66d70 100644 --- a/testsuite/tests/cabal/cabal01/test.cabal +++ b/testsuite/tests/cabal/cabal01/test.cabal @@ -7,10 +7,10 @@ Extensions: ForeignFunctionInterface Build-depends: base>=1.0 Executable: testA -Other-Modules: A, MainA +Other-Modules: A Main-is: MainA.hs Extensions: OverlappingInstances Executable: testB -Other-Modules: B.A, B.MainB +Other-Modules: B.A Main-is: B/MainB.hs From git at git.haskell.org Fri Jun 23 18:52:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jun 2017 18:52:02 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Use actual universal tvs in check for naughty record selectors (0e2839a) Message-ID: <20170623185202.ED1773A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/0e2839a2474deb0b7a24e6cd9de0a08a35bd7732/ghc >--------------------------------------------------------------- commit 0e2839a2474deb0b7a24e6cd9de0a08a35bd7732 Author: Matthew Pickering Date: Fri Jun 23 11:40:50 2017 -0400 Use actual universal tvs in check for naughty record selectors The naughty record selector check means to limit selectors which would lead to existential tyvars escaping their scope. With record pattern synonyms, there are situations where universal tyvars don't appear in the result type, for example: ``` pattern ReadP :: Read a => a -> String pattern ReadP{readp} <- (read -> readp) ``` This is a similar issue to #11224 where we assumed that we can decide which variables are universal and which are existential by the syntactic check of seeing which appear in the result type. The fix is to use `univ_tvs` from `conLikeFullSig` rather than the previous approximation. But we must also remember to apply `EqSpec`s so we use the free variables from `inst_tys` which is precisely `univ_tvs` with `EqSpecs` applied. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3649 (cherry picked from commit 9077120918b78f5152bf3596fe6df07b91cead79) >--------------------------------------------------------------- 0e2839a2474deb0b7a24e6cd9de0a08a35bd7732 compiler/typecheck/TcTyDecls.hs | 2 +- testsuite/tests/patsyn/should_run/records-run.hs | 7 +++++++ testsuite/tests/patsyn/should_run/records-run.stdout | 1 + 3 files changed, 9 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcTyDecls.hs b/compiler/typecheck/TcTyDecls.hs index 2933890..9e69e1f 100644 --- a/compiler/typecheck/TcTyDecls.hs +++ b/compiler/typecheck/TcTyDecls.hs @@ -847,7 +847,7 @@ mkOneRecordSelector all_cons idDetails fl -- Selector type; Note [Polymorphic selectors] field_ty = conLikeFieldType con1 lbl - data_tvs = tyCoVarsOfTypeWellScoped data_ty + data_tvs = tyCoVarsOfTypesWellScoped inst_tys data_tv_set= mkVarSet data_tvs is_naughty = not (tyCoVarsOfType field_ty `subVarSet` data_tv_set) (field_tvs, field_theta, field_tau) = tcSplitSigmaTy field_ty diff --git a/testsuite/tests/patsyn/should_run/records-run.hs b/testsuite/tests/patsyn/should_run/records-run.hs index 19a6bb2..1719045 100644 --- a/testsuite/tests/patsyn/should_run/records-run.hs +++ b/testsuite/tests/patsyn/should_run/records-run.hs @@ -1,4 +1,6 @@ {-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE ViewPatterns #-} module Main where @@ -6,9 +8,14 @@ pattern Bi{a, b} = (a, b) foo = ("a","b") +pattern ReadP :: Read a => a -> String +pattern ReadP {readp} <- (read -> readp) + main = do print foo print (a foo) print (b foo) print (foo {a = "c"}) print (foo {a = "fst", b = "snd"}) + + print (readp @Int "5") diff --git a/testsuite/tests/patsyn/should_run/records-run.stdout b/testsuite/tests/patsyn/should_run/records-run.stdout index a0878c7..e76be9c 100644 --- a/testsuite/tests/patsyn/should_run/records-run.stdout +++ b/testsuite/tests/patsyn/should_run/records-run.stdout @@ -3,3 +3,4 @@ "b" ("c","b") ("fst","snd") +5 From git at git.haskell.org Fri Jun 23 18:52:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jun 2017 18:52:05 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: testsuite: Fix cabal01 for real this time (a6774e1) Message-ID: <20170623185205.A1CBB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/a6774e1d70f18f5c05279453d62fb3bcc7f07d7e/ghc >--------------------------------------------------------------- commit a6774e1d70f18f5c05279453d62fb3bcc7f07d7e 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. >--------------------------------------------------------------- a6774e1d70f18f5c05279453d62fb3bcc7f07d7e 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 Fri Jun 23 18:52:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jun 2017 18:52:08 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: testsuite: Bump Haddock performance metrics (8df27aa) Message-ID: <20170623185208.5737C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/8df27aaae0310ba40ec9cc9202a8d57167d509f3/ghc >--------------------------------------------------------------- commit 8df27aaae0310ba40ec9cc9202a8d57167d509f3 Author: Ben Gamari Date: Fri Jun 23 14:51:01 2017 -0400 testsuite: Bump Haddock performance metrics >--------------------------------------------------------------- 8df27aaae0310ba40ec9cc9202a8d57167d509f3 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 ef3ad38..24a73fd 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), 19573969096, 5) + ,(wordsize(64), 18122310128, 5) # 2012-08-14: 5920822352 (amd64/Linux) # 2012-09-20: 5829972376 (amd64/Linux) # 2012-10-08: 5902601224 (amd64/Linux) @@ -40,6 +40,7 @@ test('haddock.base', # 2017-02-17: 38425793776 (x86_64/Linux) - Generalize kind of (->) # 2017-02-12: 25592972912 (x86_64/Linux) - Type-indexed Typeable # 2017-06-16: 19573969096 (x86_64/Linux) - Don't desugar for haddock + # 2017-06-23: 18122310128 (x86_64/Linux) - Use getNameToInstancesIndex ,(platform('i386-unknown-mingw32'), 2885173512, 5) # 2013-02-10: 3358693084 (x86/Windows) @@ -134,7 +135,7 @@ test('haddock.compiler', [extra_files(['../../../../compiler/stage2/haddock.t']), unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 55777283352, 10) + [(wordsize(64), 48049549248, 10) # 2012-08-14: 26070600504 (amd64/Linux) # 2012-08-29: 26353100288 (amd64/Linux, new CG) # 2012-09-18: 26882813032 (amd64/Linux) @@ -152,6 +153,7 @@ test('haddock.compiler', # 2016-11-29: 60911147344 (amd64/Linux) unknown cause # 2017-02-11: 62070477608 (amd64/Linux) OccurAnal / One-Shot (#13227) (and others) # 2017-02-25: 55777283352 (amd64/Linux) Early inline patch + # 2017-06-23: 48049549248 (amd64/Linux) Use getNameToInstancesIndex ,(platform('i386-unknown-mingw32'), 367546388, 10) # 2012-10-30: 13773051312 (x86/Windows) From git at git.haskell.org Fri Jun 23 20:35:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jun 2017 20:35:17 +0000 (UTC) Subject: [commit: ghc] master: users guide: Rephrasing (a48464a) Message-ID: <20170623203517.99F0B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a48464a7d2858bad28cfd1f393e82589825e62db/ghc >--------------------------------------------------------------- commit a48464a7d2858bad28cfd1f393e82589825e62db Author: Ben Gamari Date: Fri Jun 23 16:34:49 2017 -0400 users guide: Rephrasing >--------------------------------------------------------------- a48464a7d2858bad28cfd1f393e82589825e62db docs/users_guide/glasgow_exts.rst | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 8846596..4a4f363 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -8957,9 +8957,9 @@ the :ghc-flag:`-XTypeApplications` flag to specify the types. For example: :: Here ``a`` is ambiguous in the definition of ``D`` but later specified to be `Int` using type applications. -So the language extension :ghc-flag:`-XAllowAmbiguousTypes` allows you to -switch off the ambiguity check. But even with ambiguity checking switched off, -GHC will complain about a function that can *never* be called, such as this one: :: +:ghc-flag:`-XAllowAmbiguousTypes` allows you to switch off the ambiguity check. +However, even with ambiguity checking switched off, GHC will complain about a +function that can *never* be called, such as this one: :: f :: (Int ~ Bool) => a -> a From git at git.haskell.org Fri Jun 23 20:35:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jun 2017 20:35:14 +0000 (UTC) Subject: [commit: ghc] master: documentation: fix trac issue #12978 (faefa7e) Message-ID: <20170623203514.D3EF33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/faefa7e57d543e7001457a53954c9b378a38ee60/ghc >--------------------------------------------------------------- commit faefa7e57d543e7001457a53954c9b378a38ee60 Author: Tibor Erdesz Date: Fri Jun 23 16:33:18 2017 -0400 documentation: fix trac issue #12978 Add reference to TypeApplications to the AllowAmbiguousType section of the user docs Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #12978 Differential Revision: https://phabricator.haskell.org/D3668 >--------------------------------------------------------------- faefa7e57d543e7001457a53954c9b378a38ee60 docs/users_guide/glasgow_exts.rst | 21 +++++++++++++++++---- 1 file changed, 17 insertions(+), 4 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index e4da54e..8846596 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -8943,10 +8943,23 @@ the function is callable. For example: :: Here ``strange``\'s type is ambiguous, but the call in ``foo`` is OK because it gives rise to a constraint ``(D Bool beta)``, which is -soluble by the ``(D Bool b)`` instance. So the language extension -:ghc-flag:`-XAllowAmbiguousTypes` allows you to switch off the ambiguity check. -But even with ambiguity checking switched off, GHC will complain about a -function that can *never* be called, such as this one: :: +soluble by the ``(D Bool b)`` instance. + +Another way of getting rid of the ambiguity at the call site is to use +the :ghc-flag:`-XTypeApplications` flag to specify the types. For example: :: + + class D a b where + h :: b + instance D Int Int where ... + + main = print (h @Int @Int) + +Here ``a`` is ambiguous in the definition of ``D`` but later specified +to be `Int` using type applications. + +So the language extension :ghc-flag:`-XAllowAmbiguousTypes` allows you to +switch off the ambiguity check. But even with ambiguity checking switched off, +GHC will complain about a function that can *never* be called, such as this one: :: f :: (Int ~ Bool) => a -> a From git at git.haskell.org Mon Jun 26 21:26:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Jun 2017 21:26:15 +0000 (UTC) Subject: [commit: ghc] master: users-guide/debug-info: Fix incorrect DWARF tags (86abe0e) Message-ID: <20170626212615.130C33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/86abe0e03f6cc2392758d6b45390177d44896113/ghc >--------------------------------------------------------------- commit 86abe0e03f6cc2392758d6b45390177d44896113 Author: Ben Gamari Date: Mon Jun 26 16:27:34 2017 -0400 users-guide/debug-info: Fix incorrect DWARF tags Reviewers: austin Subscribers: rwbarton, thomie, niteria Differential Revision: https://phabricator.haskell.org/D3675 >--------------------------------------------------------------- 86abe0e03f6cc2392758d6b45390177d44896113 docs/users_guide/debug-info.rst | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/docs/users_guide/debug-info.rst b/docs/users_guide/debug-info.rst index 2f192f2..a0aade5 100644 --- a/docs/users_guide/debug-info.rst +++ b/docs/users_guide/debug-info.rst @@ -291,19 +291,19 @@ changes outside the span are guaranteed not to affect the code in the block. Spans are described with the following attributes, -``DW_AT_ghc_span_file`` (0x2b10, string) +``DW_AT_ghc_span_file`` (0x2b00, string) the name of the source file -``DW_AT_ghc_span_start_line`` (0x2b11, integer) +``DW_AT_ghc_span_start_line`` (0x2b01, integer) the line number of the beginning of the span -``DW_AT_ghc_span_start_col`` (0x2b11, integer) +``DW_AT_ghc_span_start_col`` (0x2b02, integer) the column number of the beginning of the span -``DW_AT_ghc_span_end_line`` (0x2b11, integer) +``DW_AT_ghc_span_end_line`` (0x2b03, integer) the line number of the end of the span -``DW_AT_ghc_span_end_col`` (0x2b11, integer) +``DW_AT_ghc_span_end_col`` (0x2b04, integer) the column number of the end of the span From git at git.haskell.org Mon Jun 26 21:26:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Jun 2017 21:26:09 +0000 (UTC) Subject: [commit: ghc] master: DWARF: Use .short to render half-machine-words (904255e) Message-ID: <20170626212609.9F0443A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/904255eb9b537103898fb5f6b73df9b53ca7fd93/ghc >--------------------------------------------------------------- commit 904255eb9b537103898fb5f6b73df9b53ca7fd93 Author: Ben Gamari Date: Mon Jun 26 16:27:11 2017 -0400 DWARF: Use .short to render half-machine-words The binutils documentation states that .short is a synonym for .word, which I assumed to mean "machine word", leading me to believe that we needed to use .hword to render half-machine-words. However, Darwin's toolchain doesn't understand .hword, so there we instead used .short. However, as it turns out the binutils documentation confusingly uses "word" to refer to a 16-bit word, so .short should work fine. Moreover, LLVM's internal assembler also doesn't understand .hword, so using .short consistently simplies things remarkably. Test Plan: Validate using binutils and LLVM internal assembler, validate on Darwin Reviewers: niteria, austin Reviewed By: niteria Subscribers: rwbarton, thomie GHC Trac Issues: #13866 Differential Revision: https://phabricator.haskell.org/D3667 >--------------------------------------------------------------- 904255eb9b537103898fb5f6b73df9b53ca7fd93 compiler/nativeGen/Dwarf/Types.hs | 9 +-------- 1 file changed, 1 insertion(+), 8 deletions(-) diff --git a/compiler/nativeGen/Dwarf/Types.hs b/compiler/nativeGen/Dwarf/Types.hs index bc278b1..3c4501f 100644 --- a/compiler/nativeGen/Dwarf/Types.hs +++ b/compiler/nativeGen/Dwarf/Types.hs @@ -517,14 +517,7 @@ pprByte x = text "\t.byte " <> ppr (fromIntegral x :: Word) -- | Assembly for a two-byte constant integer pprHalf :: Word16 -> SDoc -pprHalf x = sdocWithPlatform $ \plat -> - -- Naturally Darwin doesn't support `.hword` and binutils uses `.short` - -- as a synonym for `.word` (but only some of the time!). The madness - -- is nearly too much to bear. - let dir = case platformOS plat of - OSDarwin -> text ".short" - _ -> text ".hword" - in text "\t" <> dir <+> ppr (fromIntegral x :: Word) +pprHalf x = text "\t.short" <+> ppr (fromIntegral x :: Word) -- | Assembly for a constant DWARF flag pprFlag :: Bool -> SDoc From git at git.haskell.org Mon Jun 26 21:26:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Jun 2017 21:26:12 +0000 (UTC) Subject: [commit: ghc] master: rts: Always collect stats (4bd4f56) Message-ID: <20170626212612.5A95E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4bd4f561d79de4d056571eca61a5249a5091c985/ghc >--------------------------------------------------------------- commit 4bd4f561d79de4d056571eca61a5249a5091c985 Author: Ben Gamari Date: Mon Jun 26 16:27:23 2017 -0400 rts: Always collect stats It seems that 12ad4d417b89462ba8e19a3c7772a931b3a93f0e enabled collection by default as its needs stats.allocated_bytes to determine whether the program has exceeded its grace limit. However, enabling stats also enables some potentially expensive times checks. In general GC statistics should be cheap to compute (relative to the GC itself), so now we always compute them. This allows us to once again disable giveStats by default. Fixes #13864. Reviewers: simonmar, austin, erikd Reviewed By: simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13864 Differential Revision: https://phabricator.haskell.org/D3669 >--------------------------------------------------------------- 4bd4f561d79de4d056571eca61a5249a5091c985 rts/RtsFlags.c | 2 +- rts/Stats.c | 124 ++++++++++++++++++++++++++++++--------------------------- 2 files changed, 67 insertions(+), 59 deletions(-) diff --git a/rts/RtsFlags.c b/rts/RtsFlags.c index 73635cf..7b10d2a 100644 --- a/rts/RtsFlags.c +++ b/rts/RtsFlags.c @@ -130,7 +130,7 @@ void initRtsFlagsDefaults(void) maxStkSize = 8 * 1024 * 1024; RtsFlags.GcFlags.statsFile = NULL; - RtsFlags.GcFlags.giveStats = COLLECT_GC_STATS; + RtsFlags.GcFlags.giveStats = NO_GC_STATS; RtsFlags.GcFlags.maxStkSize = maxStkSize / sizeof(W_); RtsFlags.GcFlags.initialStkSize = 1024 / sizeof(W_); diff --git a/rts/Stats.c b/rts/Stats.c index e31d124..b0c1be0 100644 --- a/rts/Stats.c +++ b/rts/Stats.c @@ -285,29 +285,76 @@ stat_endGC (Capability *cap, gc_thread *gct, W_ live, W_ copied, W_ slop, uint32_t gen, uint32_t par_n_threads, W_ par_max_copied) { - if (RtsFlags.GcFlags.giveStats != NO_GC_STATS || - rtsConfig.gcDoneHook != NULL || - RtsFlags.ProfFlags.doHeapProfile) // heap profiling needs GC_tot_time - { - // ------------------------------------------------- - // Collect all the stats about this GC in stats.gc - - stats.gc.gen = gen; - stats.gc.threads = par_n_threads; + // ------------------------------------------------- + // Collect all the stats about this GC in stats.gc. We always do this since + // it's relatively cheap and we need allocated_bytes to catch heap + // overflows. + + stats.gc.gen = gen; + stats.gc.threads = par_n_threads; + + uint64_t tot_alloc_bytes = calcTotalAllocated() * sizeof(W_); + + // allocated since the last GC + stats.gc.allocated_bytes = tot_alloc_bytes - stats.allocated_bytes; + + stats.gc.live_bytes = live * sizeof(W_); + stats.gc.large_objects_bytes = calcTotalLargeObjectsW() * sizeof(W_); + stats.gc.compact_bytes = calcTotalCompactW() * sizeof(W_); + stats.gc.slop_bytes = slop * sizeof(W_); + stats.gc.mem_in_use_bytes = mblocks_allocated * MBLOCK_SIZE; + stats.gc.copied_bytes = copied * sizeof(W_); + stats.gc.par_max_copied_bytes = par_max_copied * sizeof(W_); + + // ------------------------------------------------- + // Update the cumulative stats + + stats.gcs++; + stats.allocated_bytes = tot_alloc_bytes; + stats.max_mem_in_use_bytes = peak_mblocks_allocated * MBLOCK_SIZE; + + GC_coll_cpu[gen] += stats.gc.cpu_ns; + GC_coll_elapsed[gen] += stats.gc.elapsed_ns; + if (GC_coll_max_pause[gen] < stats.gc.elapsed_ns) { + GC_coll_max_pause[gen] = stats.gc.elapsed_ns; + } - uint64_t tot_alloc_bytes = calcTotalAllocated() * sizeof(W_); + stats.copied_bytes += stats.gc.copied_bytes; + if (par_n_threads > 1) { + stats.par_copied_bytes += stats.gc.copied_bytes; + stats.cumulative_par_max_copied_bytes += + stats.gc.par_max_copied_bytes; + } + stats.gc_cpu_ns += stats.gc.cpu_ns; + stats.gc_elapsed_ns += stats.gc.elapsed_ns; - // allocated since the last GC - stats.gc.allocated_bytes = tot_alloc_bytes - stats.allocated_bytes; + if (gen == RtsFlags.GcFlags.generations-1) { // major GC? + stats.major_gcs++; + if (stats.gc.live_bytes > stats.max_live_bytes) { + stats.max_live_bytes = stats.gc.live_bytes; + } + if (stats.gc.large_objects_bytes > stats.max_large_objects_bytes) { + stats.max_large_objects_bytes = stats.gc.large_objects_bytes; + } + if (stats.gc.compact_bytes > stats.max_compact_bytes) { + stats.max_compact_bytes = stats.gc.compact_bytes; + } + if (stats.gc.slop_bytes > stats.max_slop_bytes) { + stats.max_slop_bytes = stats.gc.slop_bytes; + } + stats.cumulative_live_bytes += stats.gc.live_bytes; + } - stats.gc.live_bytes = live * sizeof(W_); - stats.gc.large_objects_bytes = calcTotalLargeObjectsW() * sizeof(W_); - stats.gc.compact_bytes = calcTotalCompactW() * sizeof(W_); - stats.gc.slop_bytes = slop * sizeof(W_); - stats.gc.mem_in_use_bytes = mblocks_allocated * MBLOCK_SIZE; - stats.gc.copied_bytes = copied * sizeof(W_); - stats.gc.par_max_copied_bytes = par_max_copied * sizeof(W_); + // ------------------------------------------------- + // Do the more expensive bits only when stats are enabled. + if (RtsFlags.GcFlags.giveStats != NO_GC_STATS || + rtsConfig.gcDoneHook != NULL || + RtsFlags.ProfFlags.doHeapProfile) // heap profiling needs GC_tot_time + { + // We only update the times when stats are explicitly enabled since + // getProcessTimes (e.g. requiring a system call) can be expensive on + // some platforms. Time current_cpu, current_elapsed; getProcessTimes(¤t_cpu, ¤t_elapsed); stats.cpu_ns = current_cpu - start_init_cpu; @@ -319,45 +366,6 @@ stat_endGC (Capability *cap, gc_thread *gct, stats.gc.cpu_ns = current_cpu - gct->gc_start_cpu; // ------------------------------------------------- - // Update the cumulative stats - - stats.gcs++; - stats.allocated_bytes = tot_alloc_bytes; - stats.max_mem_in_use_bytes = peak_mblocks_allocated * MBLOCK_SIZE; - - GC_coll_cpu[gen] += stats.gc.cpu_ns; - GC_coll_elapsed[gen] += stats.gc.elapsed_ns; - if (GC_coll_max_pause[gen] < stats.gc.elapsed_ns) { - GC_coll_max_pause[gen] = stats.gc.elapsed_ns; - } - - stats.copied_bytes += stats.gc.copied_bytes; - if (par_n_threads > 1) { - stats.par_copied_bytes += stats.gc.copied_bytes; - stats.cumulative_par_max_copied_bytes += - stats.gc.par_max_copied_bytes; - } - stats.gc_cpu_ns += stats.gc.cpu_ns; - stats.gc_elapsed_ns += stats.gc.elapsed_ns; - - if (gen == RtsFlags.GcFlags.generations-1) { // major GC? - stats.major_gcs++; - if (stats.gc.live_bytes > stats.max_live_bytes) { - stats.max_live_bytes = stats.gc.live_bytes; - } - if (stats.gc.large_objects_bytes > stats.max_large_objects_bytes) { - stats.max_large_objects_bytes = stats.gc.large_objects_bytes; - } - if (stats.gc.compact_bytes > stats.max_compact_bytes) { - stats.max_compact_bytes = stats.gc.compact_bytes; - } - if (stats.gc.slop_bytes > stats.max_slop_bytes) { - stats.max_slop_bytes = stats.gc.slop_bytes; - } - stats.cumulative_live_bytes += stats.gc.live_bytes; - } - - // ------------------------------------------------- // Emit events to the event log // Has to be emitted while all caps stopped for GC, but before GC_END. From git at git.haskell.org Mon Jun 26 22:25:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Jun 2017 22:25:31 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: documentation: fix trac issue #12978 (ba15d18) Message-ID: <20170626222531.974FE3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/ba15d1879438ad19e5cdd3f38c2c5f449e6e911c/ghc >--------------------------------------------------------------- commit ba15d1879438ad19e5cdd3f38c2c5f449e6e911c Author: Tibor Erdesz Date: Fri Jun 23 16:33:18 2017 -0400 documentation: fix trac issue #12978 Add reference to TypeApplications to the AllowAmbiguousType section of the user docs Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #12978 Differential Revision: https://phabricator.haskell.org/D3668 (cherry picked from commit faefa7e57d543e7001457a53954c9b378a38ee60) >--------------------------------------------------------------- ba15d1879438ad19e5cdd3f38c2c5f449e6e911c docs/users_guide/glasgow_exts.rst | 21 +++++++++++++++++---- 1 file changed, 17 insertions(+), 4 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 5b71c02..ecd1ebd 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -8848,10 +8848,23 @@ the function is callable. For example: :: Here ``strange``\'s type is ambiguous, but the call in ``foo`` is OK because it gives rise to a constraint ``(D Bool beta)``, which is -soluble by the ``(D Bool b)`` instance. So the language extension -:ghc-flag:`-XAllowAmbiguousTypes` allows you to switch off the ambiguity check. -But even with ambiguity checking switched off, GHC will complain about a -function that can *never* be called, such as this one: :: +soluble by the ``(D Bool b)`` instance. + +Another way of getting rid of the ambiguity at the call site is to use +the :ghc-flag:`-XTypeApplications` flag to specify the types. For example: :: + + class D a b where + h :: b + instance D Int Int where ... + + main = print (h @Int @Int) + +Here ``a`` is ambiguous in the definition of ``D`` but later specified +to be `Int` using type applications. + +So the language extension :ghc-flag:`-XAllowAmbiguousTypes` allows you to +switch off the ambiguity check. But even with ambiguity checking switched off, +GHC will complain about a function that can *never* be called, such as this one: :: f :: (Int ~ Bool) => a -> a From git at git.haskell.org Mon Jun 26 22:25:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Jun 2017 22:25:34 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: users guide: Rephrasing (efc6073) Message-ID: <20170626222534.5D3933A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/efc6073c31cc7065b5016f3c041d1f578c763b63/ghc >--------------------------------------------------------------- commit efc6073c31cc7065b5016f3c041d1f578c763b63 Author: Ben Gamari Date: Fri Jun 23 16:34:49 2017 -0400 users guide: Rephrasing (cherry picked from commit a48464a7d2858bad28cfd1f393e82589825e62db) >--------------------------------------------------------------- efc6073c31cc7065b5016f3c041d1f578c763b63 docs/users_guide/glasgow_exts.rst | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index ecd1ebd..c738862 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -8862,9 +8862,9 @@ the :ghc-flag:`-XTypeApplications` flag to specify the types. For example: :: Here ``a`` is ambiguous in the definition of ``D`` but later specified to be `Int` using type applications. -So the language extension :ghc-flag:`-XAllowAmbiguousTypes` allows you to -switch off the ambiguity check. But even with ambiguity checking switched off, -GHC will complain about a function that can *never* be called, such as this one: :: +:ghc-flag:`-XAllowAmbiguousTypes` allows you to switch off the ambiguity check. +However, even with ambiguity checking switched off, GHC will complain about a +function that can *never* be called, such as this one: :: f :: (Int ~ Bool) => a -> a From git at git.haskell.org Mon Jun 26 22:25:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Jun 2017 22:25:37 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: DWARF: Use .short to render half-machine-words (bed2ff7) Message-ID: <20170626222537.14E783A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/bed2ff7f26319d7ee4c5be0ee66c48e13c08a1a5/ghc >--------------------------------------------------------------- commit bed2ff7f26319d7ee4c5be0ee66c48e13c08a1a5 Author: Ben Gamari Date: Mon Jun 26 16:27:11 2017 -0400 DWARF: Use .short to render half-machine-words The binutils documentation states that .short is a synonym for .word, which I assumed to mean "machine word", leading me to believe that we needed to use .hword to render half-machine-words. However, Darwin's toolchain doesn't understand .hword, so there we instead used .short. However, as it turns out the binutils documentation confusingly uses "word" to refer to a 16-bit word, so .short should work fine. Moreover, LLVM's internal assembler also doesn't understand .hword, so using .short consistently simplies things remarkably. Test Plan: Validate using binutils and LLVM internal assembler, validate on Darwin Reviewers: niteria, austin Reviewed By: niteria Subscribers: rwbarton, thomie GHC Trac Issues: #13866 Differential Revision: https://phabricator.haskell.org/D3667 (cherry picked from commit 904255eb9b537103898fb5f6b73df9b53ca7fd93) >--------------------------------------------------------------- bed2ff7f26319d7ee4c5be0ee66c48e13c08a1a5 compiler/nativeGen/Dwarf/Types.hs | 9 +-------- 1 file changed, 1 insertion(+), 8 deletions(-) diff --git a/compiler/nativeGen/Dwarf/Types.hs b/compiler/nativeGen/Dwarf/Types.hs index d4d8e24..e799f43 100644 --- a/compiler/nativeGen/Dwarf/Types.hs +++ b/compiler/nativeGen/Dwarf/Types.hs @@ -516,14 +516,7 @@ pprByte x = text "\t.byte " <> ppr (fromIntegral x :: Word) -- | Assembly for a two-byte constant integer pprHalf :: Word16 -> SDoc -pprHalf x = sdocWithPlatform $ \plat -> - -- Naturally Darwin doesn't support `.hword` and binutils uses `.short` - -- as a synonym for `.word` (but only some of the time!). The madness - -- is nearly too much to bear. - let dir = case platformOS plat of - OSDarwin -> text ".short" - _ -> text ".hword" - in text "\t" <> dir <+> ppr (fromIntegral x :: Word) +pprHalf x = text "\t.short" <+> ppr (fromIntegral x :: Word) -- | Assembly for a constant DWARF flag pprFlag :: Bool -> SDoc From git at git.haskell.org Mon Jun 26 22:25:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Jun 2017 22:25:42 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: users-guide/debug-info: Fix incorrect DWARF tags (09f5582) Message-ID: <20170626222542.7FB4A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/09f558220d421330b9be63f529aa71980e745ba1/ghc >--------------------------------------------------------------- commit 09f558220d421330b9be63f529aa71980e745ba1 Author: Ben Gamari Date: Mon Jun 26 16:27:34 2017 -0400 users-guide/debug-info: Fix incorrect DWARF tags Reviewers: austin Subscribers: rwbarton, thomie, niteria Differential Revision: https://phabricator.haskell.org/D3675 (cherry picked from commit 86abe0e03f6cc2392758d6b45390177d44896113) >--------------------------------------------------------------- 09f558220d421330b9be63f529aa71980e745ba1 docs/users_guide/debug-info.rst | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/docs/users_guide/debug-info.rst b/docs/users_guide/debug-info.rst index 2f192f2..a0aade5 100644 --- a/docs/users_guide/debug-info.rst +++ b/docs/users_guide/debug-info.rst @@ -291,19 +291,19 @@ changes outside the span are guaranteed not to affect the code in the block. Spans are described with the following attributes, -``DW_AT_ghc_span_file`` (0x2b10, string) +``DW_AT_ghc_span_file`` (0x2b00, string) the name of the source file -``DW_AT_ghc_span_start_line`` (0x2b11, integer) +``DW_AT_ghc_span_start_line`` (0x2b01, integer) the line number of the beginning of the span -``DW_AT_ghc_span_start_col`` (0x2b11, integer) +``DW_AT_ghc_span_start_col`` (0x2b02, integer) the column number of the beginning of the span -``DW_AT_ghc_span_end_line`` (0x2b11, integer) +``DW_AT_ghc_span_end_line`` (0x2b03, integer) the line number of the end of the span -``DW_AT_ghc_span_end_col`` (0x2b11, integer) +``DW_AT_ghc_span_end_col`` (0x2b04, integer) the column number of the end of the span From git at git.haskell.org Mon Jun 26 22:25:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Jun 2017 22:25:39 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: rts: Always collect stats (f19ab07) Message-ID: <20170626222539.C726B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/f19ab07b660589bc7cc04073b9c91fac4be384e1/ghc >--------------------------------------------------------------- commit f19ab07b660589bc7cc04073b9c91fac4be384e1 Author: Ben Gamari Date: Mon Jun 26 16:27:23 2017 -0400 rts: Always collect stats It seems that 12ad4d417b89462ba8e19a3c7772a931b3a93f0e enabled collection by default as its needs stats.allocated_bytes to determine whether the program has exceeded its grace limit. However, enabling stats also enables some potentially expensive times checks. In general GC statistics should be cheap to compute (relative to the GC itself), so now we always compute them. This allows us to once again disable giveStats by default. Fixes #13864. Reviewers: simonmar, austin, erikd Reviewed By: simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13864 Differential Revision: https://phabricator.haskell.org/D3669 (cherry picked from commit 4bd4f561d79de4d056571eca61a5249a5091c985) >--------------------------------------------------------------- f19ab07b660589bc7cc04073b9c91fac4be384e1 rts/RtsFlags.c | 2 +- rts/Stats.c | 124 ++++++++++++++++++++++++++++++--------------------------- 2 files changed, 67 insertions(+), 59 deletions(-) diff --git a/rts/RtsFlags.c b/rts/RtsFlags.c index 8d71354..0a12ba3 100644 --- a/rts/RtsFlags.c +++ b/rts/RtsFlags.c @@ -130,7 +130,7 @@ void initRtsFlagsDefaults(void) maxStkSize = 8 * 1024 * 1024; RtsFlags.GcFlags.statsFile = NULL; - RtsFlags.GcFlags.giveStats = COLLECT_GC_STATS; + RtsFlags.GcFlags.giveStats = NO_GC_STATS; RtsFlags.GcFlags.maxStkSize = maxStkSize / sizeof(W_); RtsFlags.GcFlags.initialStkSize = 1024 / sizeof(W_); diff --git a/rts/Stats.c b/rts/Stats.c index 5f5fa58..552200c 100644 --- a/rts/Stats.c +++ b/rts/Stats.c @@ -285,29 +285,76 @@ stat_endGC (Capability *cap, gc_thread *gct, W_ live, W_ copied, W_ slop, uint32_t gen, uint32_t par_n_threads, W_ par_max_copied) { - if (RtsFlags.GcFlags.giveStats != NO_GC_STATS || - rtsConfig.gcDoneHook != NULL || - RtsFlags.ProfFlags.doHeapProfile) // heap profiling needs GC_tot_time - { - // ------------------------------------------------- - // Collect all the stats about this GC in stats.gc - - stats.gc.gen = gen; - stats.gc.threads = par_n_threads; + // ------------------------------------------------- + // Collect all the stats about this GC in stats.gc. We always do this since + // it's relatively cheap and we need allocated_bytes to catch heap + // overflows. + + stats.gc.gen = gen; + stats.gc.threads = par_n_threads; + + uint64_t tot_alloc_bytes = calcTotalAllocated() * sizeof(W_); + + // allocated since the last GC + stats.gc.allocated_bytes = tot_alloc_bytes - stats.allocated_bytes; + + stats.gc.live_bytes = live * sizeof(W_); + stats.gc.large_objects_bytes = calcTotalLargeObjectsW() * sizeof(W_); + stats.gc.compact_bytes = calcTotalCompactW() * sizeof(W_); + stats.gc.slop_bytes = slop * sizeof(W_); + stats.gc.mem_in_use_bytes = mblocks_allocated * MBLOCK_SIZE; + stats.gc.copied_bytes = copied * sizeof(W_); + stats.gc.par_max_copied_bytes = par_max_copied * sizeof(W_); + + // ------------------------------------------------- + // Update the cumulative stats + + stats.gcs++; + stats.allocated_bytes = tot_alloc_bytes; + stats.max_mem_in_use_bytes = peak_mblocks_allocated * MBLOCK_SIZE; + + GC_coll_cpu[gen] += stats.gc.cpu_ns; + GC_coll_elapsed[gen] += stats.gc.elapsed_ns; + if (GC_coll_max_pause[gen] < stats.gc.elapsed_ns) { + GC_coll_max_pause[gen] = stats.gc.elapsed_ns; + } - uint64_t tot_alloc_bytes = calcTotalAllocated() * sizeof(W_); + stats.copied_bytes += stats.gc.copied_bytes; + if (par_n_threads > 1) { + stats.par_copied_bytes += stats.gc.copied_bytes; + stats.cumulative_par_max_copied_bytes += + stats.gc.par_max_copied_bytes; + } + stats.gc_cpu_ns += stats.gc.cpu_ns; + stats.gc_elapsed_ns += stats.gc.elapsed_ns; - // allocated since the last GC - stats.gc.allocated_bytes = tot_alloc_bytes - stats.allocated_bytes; + if (gen == RtsFlags.GcFlags.generations-1) { // major GC? + stats.major_gcs++; + if (stats.gc.live_bytes > stats.max_live_bytes) { + stats.max_live_bytes = stats.gc.live_bytes; + } + if (stats.gc.large_objects_bytes > stats.max_large_objects_bytes) { + stats.max_large_objects_bytes = stats.gc.large_objects_bytes; + } + if (stats.gc.compact_bytes > stats.max_compact_bytes) { + stats.max_compact_bytes = stats.gc.compact_bytes; + } + if (stats.gc.slop_bytes > stats.max_slop_bytes) { + stats.max_slop_bytes = stats.gc.slop_bytes; + } + stats.cumulative_live_bytes += stats.gc.live_bytes; + } - stats.gc.live_bytes = live * sizeof(W_); - stats.gc.large_objects_bytes = calcTotalLargeObjectsW() * sizeof(W_); - stats.gc.compact_bytes = calcTotalCompactW() * sizeof(W_); - stats.gc.slop_bytes = slop * sizeof(W_); - stats.gc.mem_in_use_bytes = mblocks_allocated * MBLOCK_SIZE; - stats.gc.copied_bytes = copied * sizeof(W_); - stats.gc.par_max_copied_bytes = par_max_copied * sizeof(W_); + // ------------------------------------------------- + // Do the more expensive bits only when stats are enabled. + if (RtsFlags.GcFlags.giveStats != NO_GC_STATS || + rtsConfig.gcDoneHook != NULL || + RtsFlags.ProfFlags.doHeapProfile) // heap profiling needs GC_tot_time + { + // We only update the times when stats are explicitly enabled since + // getProcessTimes (e.g. requiring a system call) can be expensive on + // some platforms. Time current_cpu, current_elapsed; getProcessTimes(¤t_cpu, ¤t_elapsed); stats.cpu_ns = current_cpu - start_init_cpu; @@ -319,45 +366,6 @@ stat_endGC (Capability *cap, gc_thread *gct, stats.gc.cpu_ns = current_cpu - gct->gc_start_cpu; // ------------------------------------------------- - // Update the cumulative stats - - stats.gcs++; - stats.allocated_bytes = tot_alloc_bytes; - stats.max_mem_in_use_bytes = peak_mblocks_allocated * MBLOCK_SIZE; - - GC_coll_cpu[gen] += stats.gc.cpu_ns; - GC_coll_elapsed[gen] += stats.gc.elapsed_ns; - if (GC_coll_max_pause[gen] < stats.gc.elapsed_ns) { - GC_coll_max_pause[gen] = stats.gc.elapsed_ns; - } - - stats.copied_bytes += stats.gc.copied_bytes; - if (par_n_threads > 1) { - stats.par_copied_bytes += stats.gc.copied_bytes; - stats.cumulative_par_max_copied_bytes += - stats.gc.par_max_copied_bytes; - } - stats.gc_cpu_ns += stats.gc.cpu_ns; - stats.gc_elapsed_ns += stats.gc.elapsed_ns; - - if (gen == RtsFlags.GcFlags.generations-1) { // major GC? - stats.major_gcs++; - if (stats.gc.live_bytes > stats.max_live_bytes) { - stats.max_live_bytes = stats.gc.live_bytes; - } - if (stats.gc.large_objects_bytes > stats.max_large_objects_bytes) { - stats.max_large_objects_bytes = stats.gc.large_objects_bytes; - } - if (stats.gc.compact_bytes > stats.max_compact_bytes) { - stats.max_compact_bytes = stats.gc.compact_bytes; - } - if (stats.gc.slop_bytes > stats.max_slop_bytes) { - stats.max_slop_bytes = stats.gc.slop_bytes; - } - stats.cumulative_live_bytes += stats.gc.live_bytes; - } - - // ------------------------------------------------- // Emit events to the event log // Has to be emitted while all caps stopped for GC, but before GC_END. From git at git.haskell.org Tue Jun 27 09:14:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:14:38 +0000 (UTC) Subject: [commit: ghc] branch 'wip/kavon-nosplit-llvm' created Message-ID: <20170627091438.C94933A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/kavon-nosplit-llvm Referencing: c6c172818a555aef09edb99ac8fae1a05b49df47 From git at git.haskell.org Tue Jun 27 09:14:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:14:41 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: bumping LLVM version to 5.0 (7338422) Message-ID: <20170627091441.820753A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/733842247d46907269282e206d8ffa13600ae916/ghc >--------------------------------------------------------------- commit 733842247d46907269282e206d8ffa13600ae916 Author: Kavon Farvardin Date: Wed May 3 16:47:56 2017 +0100 bumping LLVM version to 5.0 >--------------------------------------------------------------- 733842247d46907269282e206d8ffa13600ae916 configure.ac | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/configure.ac b/configure.ac index 46e37ab..6b52a33 100644 --- a/configure.ac +++ b/configure.ac @@ -574,7 +574,7 @@ RANLIB="$RanlibCmd" # tools we are looking for. In the past, GHC supported a number of # versions of LLVM simultaneously, but that stopped working around # 3.5/3.6 release of LLVM. -LlvmVersion=3.9 +LlvmVersion=5.0 AC_SUBST([LlvmVersion]) sUPPORTED_LLVM_VERSION=$(echo \($LlvmVersion\) | sed 's/\./,/') AC_DEFINE_UNQUOTED([sUPPORTED_LLVM_VERSION], ${sUPPORTED_LLVM_VERSION}, [The supported LLVM version number]) From git at git.haskell.org Tue Jun 27 09:14:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:14:48 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: turning off splitting when using LLVM to start things off (b0bbfd2) Message-ID: <20170627091448.2E5AF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/b0bbfd23b2db1e6cc6e90c35d102d408309f3ebb/ghc >--------------------------------------------------------------- commit b0bbfd23b2db1e6cc6e90c35d102d408309f3ebb Author: Kavon Farvardin Date: Wed May 10 17:36:34 2017 +0100 turning off splitting when using LLVM to start things off >--------------------------------------------------------------- b0bbfd23b2db1e6cc6e90c35d102d408309f3ebb compiler/cmm/CmmPipeline.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/cmm/CmmPipeline.hs b/compiler/cmm/CmmPipeline.hs index a0fe4b1..d43327f 100644 --- a/compiler/cmm/CmmPipeline.hs +++ b/compiler/cmm/CmmPipeline.hs @@ -158,7 +158,8 @@ cpsTop hsc_env proc = -- tablesNextToCode is off. The latter is because we have no -- label to put on info tables for basic blocks that are not -- the entry point. - splitting_proc_points = hscTarget dflags /= HscAsm + target = hscTarget dflags + splitting_proc_points = not (target == HscAsm || target == HscLlvm) || not (tablesNextToCode dflags) || -- Note [inconsistent-pic-reg] usingInconsistentPicReg From git at git.haskell.org Tue Jun 27 09:14:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:14:45 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: Merge branch 'master' into no-split (ed3cb56) Message-ID: <20170627091445.7B9DB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/ed3cb561a8a2f81e54602a55be05ae5991777c25/ghc >--------------------------------------------------------------- commit ed3cb561a8a2f81e54602a55be05ae5991777c25 Merge: 7338422 239418c Author: Kavon Farvardin Date: Wed May 3 17:18:09 2017 +0100 Merge branch 'master' into no-split catching up to master 239418cf94dede0f116bb859d1bb95891235eb76 >--------------------------------------------------------------- ed3cb561a8a2f81e54602a55be05ae5991777c25 compiler/basicTypes/OccName.hs | 23 +- compiler/codeGen/StgCmmPrim.hs | 6 +- compiler/coreSyn/CoreLint.hs | 4 +- compiler/coreSyn/CoreSubst.hs | 2 +- compiler/coreSyn/CoreSyn.hs | 3 +- compiler/coreSyn/CoreTidy.hs | 8 +- compiler/deSugar/Check.hs | 2 +- compiler/deSugar/DsArrows.hs | 4 +- compiler/deSugar/DsExpr.hs | 262 ++++++--- compiler/deSugar/DsMonad.hs | 3 +- compiler/hsSyn/HsExpr.hs | 3 + compiler/hsSyn/HsUtils.hs | 7 +- compiler/llvmGen/LlvmCodeGen/Ppr.hs | 72 ++- compiler/llvmGen/LlvmMangler.hs | 11 +- compiler/main/TidyPgm.hs | 5 +- compiler/nativeGen/PPC/CodeGen.hs | 8 + compiler/nativeGen/PPC/Instr.hs | 3 + compiler/nativeGen/PPC/Ppr.hs | 1 + compiler/rename/RnEnv.hs | 2 +- compiler/simplCore/SetLevels.hs | 39 +- compiler/simplCore/SimplEnv.hs | 237 ++++---- compiler/simplCore/SimplMonad.hs | 20 +- compiler/simplCore/SimplUtils.hs | 125 ++-- compiler/simplCore/Simplify.hs | 627 +++++++++++---------- compiler/simplStg/StgCse.hs | 2 +- compiler/specialise/SpecConstr.hs | 315 +++++++---- compiler/typecheck/TcAnnotations.hs | 25 +- compiler/typecheck/TcBinds.hs | 2 +- compiler/typecheck/TcCanonical.hs | 98 +--- compiler/typecheck/TcExpr.hs | 20 +- compiler/typecheck/TcFlatten.hs | 88 ++- compiler/typecheck/TcMatches.hs | 4 +- compiler/typecheck/TcRnTypes.hs | 21 +- compiler/typecheck/TcSMonad.hs | 1 + compiler/typecheck/TcSplice.hs | 4 +- compiler/types/Kind.hs | 40 -- compiler/types/TyCoRep.hs | 4 +- compiler/types/Type.hs | 146 ++--- compiler/types/Type.hs-boot | 3 +- configure.ac | 2 +- docs/users_guide/glasgow_exts.rst | 2 +- libraries/array | 2 +- libraries/base/System/IO.hs | 20 +- mk/warnings.mk | 4 +- rts/Linker.c | 56 +- rts/linker/Elf.c | 166 +++++- rts/linker/Elf.h | 4 + rts/linker/LoadArchive.c | 5 + testsuite/tests/codeGen/should_compile/T13233.hs | 12 - testsuite/tests/codeGen/should_compile/all.T | 1 - testsuite/tests/codeGen/should_fail/T13233.hs | 27 + testsuite/tests/codeGen/should_fail/T13233.stderr | 24 + testsuite/tests/codeGen/should_fail/all.T | 1 + testsuite/tests/perf/compiler/all.T | 21 +- testsuite/tests/perf/should_run/T13623.hs | 82 +++ testsuite/tests/perf/should_run/T13623.stdout | 1 + testsuite/tests/perf/should_run/all.T | 8 + .../tests/simplCore/should_compile/T12603.stdout | 2 +- .../tests/simplCore/should_compile/T3234.stderr | 10 +- testsuite/tests/stage1/T13609.hs | 5 + testsuite/tests/stage1/T13609.stderr | 3 + testsuite/tests/stage1/all.T | 1 + testsuite/tests/typecheck/should_compile/Makefile | 6 + testsuite/tests/typecheck/should_compile/T13333.hs | 28 + testsuite/tests/typecheck/should_compile/T13585.hs | 5 + .../tests/typecheck/should_compile/T13585a.hs | 81 +++ .../tests/typecheck/should_compile/T13585b.hs | 7 + testsuite/tests/typecheck/should_compile/all.T | 2 + .../tests/typecheck/should_fail/T10619.stderr | 4 +- 69 files changed, 1815 insertions(+), 1027 deletions(-) From git at git.haskell.org Tue Jun 27 09:14:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:14:50 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: adding spot to expand non-tail calls correctly (cd0746f) Message-ID: <20170627091450.D5AC43A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/cd0746f93e1f299fcaa51fb3aebd7ea575b5ac62/ghc >--------------------------------------------------------------- commit cd0746f93e1f299fcaa51fb3aebd7ea575b5ac62 Author: Kavon Farvardin Date: Wed May 10 19:23:03 2017 +0100 adding spot to expand non-tail calls correctly >--------------------------------------------------------------- cd0746f93e1f299fcaa51fb3aebd7ea575b5ac62 compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 0381324..43690e9 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -126,9 +126,12 @@ stmtToInstrs stmt = case stmt of CmmUnsafeForeignCall target res args -> genCall target res args - -- Tail call + -- Cmm call CmmCall { cml_target = arg, - cml_args_regs = live } -> genJump arg live + cml_args_regs = live, + cml_cont = maybeCont } -> case maybeCont of + Nothing -> genJump arg live -- Tail call + Just cont -> panic "todo: handle non-tail CmmCall" _ -> panic "Llvm.CodeGen.stmtToInstrs" From git at git.haskell.org Tue Jun 27 09:14:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:14:53 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: see below. do not write RA to stack with LLVM. (b00df64) Message-ID: <20170627091453.876683A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/b00df644588506f57bb5515b0b3cc9d1b2078351/ghc >--------------------------------------------------------------- commit b00df644588506f57bb5515b0b3cc9d1b2078351 Author: Kavon Farvardin Date: Fri May 12 15:35:32 2017 +0100 see below. do not write RA to stack with LLVM. only for native calls right now. 1. this breaks the fragile [diamond proc point] optimization, though there is a better way to implement that optimization through the use of headers for proc-points (sort of like critical edge splitting). 2. need to do the same for foreign calls with LLVM too. >--------------------------------------------------------------- b00df644588506f57bb5515b0b3cc9d1b2078351 compiler/cmm/MkGraph.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/cmm/MkGraph.hs b/compiler/cmm/MkGraph.hs index 81d9c0f..0c71210 100644 --- a/compiler/cmm/MkGraph.hs +++ b/compiler/cmm/MkGraph.hs @@ -361,8 +361,11 @@ copyOutOflow dflags conv transfer area actuals updfr_off extra_stack_stuff -- the return address if making a call case transfer of Call -> - ([(CmmLit (CmmBlock id), StackParam init_offset)], - widthInBytes (wordWidth dflags)) + if hscTarget dflags == HscLlvm + then ([], widthInBytes (wordWidth dflags)) + else + ([(CmmLit (CmmBlock id), StackParam init_offset)], + widthInBytes (wordWidth dflags)) JumpRet -> ([], widthInBytes (wordWidth dflags)) From git at git.haskell.org Tue Jun 27 09:14:56 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:14:56 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: adding a note about why we check for HscLlvm (02eb265) Message-ID: <20170627091456.3AA1C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/02eb265a1998cfed1630936c60af884e899d63f4/ghc >--------------------------------------------------------------- commit 02eb265a1998cfed1630936c60af884e899d63f4 Author: Kavon Farvardin Date: Fri May 12 17:36:07 2017 +0100 adding a note about why we check for HscLlvm >--------------------------------------------------------------- 02eb265a1998cfed1630936c60af884e899d63f4 compiler/cmm/MkGraph.hs | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/compiler/cmm/MkGraph.hs b/compiler/cmm/MkGraph.hs index 0c71210..eca5fbf 100644 --- a/compiler/cmm/MkGraph.hs +++ b/compiler/cmm/MkGraph.hs @@ -329,6 +329,12 @@ copyIn dflags conv area formals extra_stk -- Factoring out the common parts of the copyout functions yielded something -- more complicated: +-- Note [llvm non-tail calls] +-- We cannot explicily store a block address to the stack when using +-- LLVM. Instead, we just leave space in the frame for the return +-- address, which LLVM's assembly code generator will fill in later +-- when it sees the CPSCALL pseudo-instruction. + data Transfer = Call | JumpRet | Jump | Ret deriving Eq copyOutOflow :: DynFlags -> Convention -> Transfer -> Area -> [CmmExpr] @@ -361,6 +367,7 @@ copyOutOflow dflags conv transfer area actuals updfr_off extra_stack_stuff -- the return address if making a call case transfer of Call -> + -- see Note [llvm non-tail calls] if hscTarget dflags == HscLlvm then ([], widthInBytes (wordWidth dflags)) else From git at git.haskell.org Tue Jun 27 09:14:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:14:58 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: added support for insertvalue instruction (48797fd) Message-ID: <20170627091458.E1E873A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/48797fd24e22c63b6419b70df3160f8be60a075e/ghc >--------------------------------------------------------------- commit 48797fd24e22c63b6419b70df3160f8be60a075e Author: Kavon Farvardin Date: Mon May 15 11:55:02 2017 +0100 added support for insertvalue instruction >--------------------------------------------------------------- 48797fd24e22c63b6419b70df3160f8be60a075e compiler/llvmGen/Llvm/AbsSyn.hs | 9 ++++++++- compiler/llvmGen/Llvm/PpLlvm.hs | 8 ++++++++ 2 files changed, 16 insertions(+), 1 deletion(-) diff --git a/compiler/llvmGen/Llvm/AbsSyn.hs b/compiler/llvmGen/Llvm/AbsSyn.hs index 45d79f5..e107cb2 100644 --- a/compiler/llvmGen/Llvm/AbsSyn.hs +++ b/compiler/llvmGen/Llvm/AbsSyn.hs @@ -241,6 +241,14 @@ data LlvmExpression | Insert LlvmVar LlvmVar LlvmVar {- | + Insert a scalar element into a structure + * val: The structure + * elt: The scalar to insert + * index: The index at which to insert within the structure + -} + | InsertV LlvmVar LlvmVar Int + + {- | Allocate amount * sizeof(tp) bytes on the heap * tp: LlvmType to reserve room for * amount: The nr of tp's which must be allocated @@ -347,4 +355,3 @@ data LlvmExpression | MExpr [MetaAnnot] LlvmExpression deriving (Eq) - diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs index 293999b..5812340 100644 --- a/compiler/llvmGen/Llvm/PpLlvm.hs +++ b/compiler/llvmGen/Llvm/PpLlvm.hs @@ -232,6 +232,7 @@ ppLlvmExpression expr Extract vec idx -> ppExtract vec idx ExtractV struct idx -> ppExtractV struct idx Insert vec elt idx -> ppInsert vec elt idx + InsertV struct elt idx -> ppInsertV struct elt idx GetElemPtr inb ptr indexes -> ppGetElementPtr inb ptr indexes Load ptr -> ppLoad ptr ALoad ord st ptr -> ppALoad ord st ptr @@ -466,6 +467,13 @@ ppInsert vec elt idx = <+> ppr (getVarType elt) <+> ppName elt <> comma <+> ppr idx +ppInsertV :: LlvmVar -> LlvmVar -> Int -> SDoc +ppInsertV struct elt idx = + text "insertvalue" + <+> ppr (getVarType struct) <+> ppName struct <> comma + <+> ppr (getVarType elt) <+> ppName elt <> comma + <+> ppr idx + ppMetaStatement :: [MetaAnnot] -> LlvmStatement -> SDoc ppMetaStatement meta stmt = ppLlvmStatement stmt <> ppMetaAnnots meta From git at git.haskell.org Tue Jun 27 09:15:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:04 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: set the return type to be a struct of the arg tys (e375009) Message-ID: <20170627091504.5BF023A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/e37500967432cdf5983fa868f168acb1c3a58c22/ghc >--------------------------------------------------------------- commit e37500967432cdf5983fa868f168acb1c3a58c22 Author: Kavon Farvardin Date: Tue May 16 09:55:48 2017 +0100 set the return type to be a struct of the arg tys >--------------------------------------------------------------- e37500967432cdf5983fa868f168acb1c3a58c22 compiler/llvmGen/LlvmCodeGen/Base.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index 8b01da8..46d01bf 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -124,9 +124,11 @@ llvmFunSig' live lbl link = do let toParams x | isPointer x = (x, [NoAlias, NoCapture]) | otherwise = (x, []) dflags <- getDynFlags - let retTy = LMFloat -- TODO: generate the struct that we will return. + -- the standard set of argument types passed/returned. + let stdConvention = map getVarType (llvmFunArgs dflags live) + let retTy = LMStructU $ stdConvention return $ LlvmFunctionDecl lbl link (llvmGhcCC dflags) retTy FixedArgs - (map (toParams . getVarType) (llvmFunArgs dflags live)) + (map toParams stdConvention) (llvmFunAlign dflags) -- | Alignment to use for functions From git at git.haskell.org Tue Jun 27 09:15:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:01 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: changing funTy so that it returns something. for now it's just a float (ec29bf7) Message-ID: <20170627091501.A793F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/ec29bf7e60a5b5f54fcdb5d21a341ca00118eeb3/ghc >--------------------------------------------------------------- commit ec29bf7e60a5b5f54fcdb5d21a341ca00118eeb3 Author: Kavon Farvardin Date: Mon May 15 15:43:17 2017 +0100 changing funTy so that it returns something. for now it's just a float >--------------------------------------------------------------- ec29bf7e60a5b5f54fcdb5d21a341ca00118eeb3 compiler/llvmGen/Llvm.hs | 3 +-- compiler/llvmGen/Llvm/Types.hs | 6 +++++ compiler/llvmGen/LlvmCodeGen/Base.hs | 3 ++- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 43 +++++++++++++++++++++------------ 4 files changed, 36 insertions(+), 19 deletions(-) diff --git a/compiler/llvmGen/Llvm.hs b/compiler/llvmGen/Llvm.hs index 8104a3a..796c5fc 100644 --- a/compiler/llvmGen/Llvm.hs +++ b/compiler/llvmGen/Llvm.hs @@ -45,7 +45,7 @@ module Llvm ( MetaExpr(..), MetaAnnot(..), MetaDecl(..), MetaId(..), -- ** Operations on the type system. - isGlobal, getLitType, getVarType, + isGlobal, getLitType, getVarType, getRetTy, getLink, getStatType, pVarLift, pVarLower, pLift, pLower, isInt, isFloat, isPointer, isVector, llvmWidthInBits, @@ -61,4 +61,3 @@ import Llvm.AbsSyn import Llvm.MetaData import Llvm.PpLlvm import Llvm.Types - diff --git a/compiler/llvmGen/Llvm/Types.hs b/compiler/llvmGen/Llvm/Types.hs index bf23cd8..6245642 100644 --- a/compiler/llvmGen/Llvm/Types.hs +++ b/compiler/llvmGen/Llvm/Types.hs @@ -267,6 +267,12 @@ getLitType (LMVectorLit ls) = LMVector (length ls) (getLitType (head ls)) getLitType (LMNullLit t) = t getLitType (LMUndefLit t) = t +-- | Return the return type of the given function or function pointer type +getRetTy :: LlvmType -> LlvmType +getRetTy (LMFunction(LlvmFunctionDecl{decReturnType = t})) = t +getRetTy (LMPointer(LMFunction(LlvmFunctionDecl{decReturnType = t}))) = t +getRetTy _ = panic "getRetTy -- not a function or function pointer!" + -- | Return the 'LlvmType' of the 'LlvmStatic' getStatType :: LlvmStatic -> LlvmType getStatType (LMStaticLit l ) = getLitType l diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index 424891f..8b01da8 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -124,7 +124,8 @@ llvmFunSig' live lbl link = do let toParams x | isPointer x = (x, [NoAlias, NoCapture]) | otherwise = (x, []) dflags <- getDynFlags - return $ LlvmFunctionDecl lbl link (llvmGhcCC dflags) LMVoid FixedArgs + let retTy = LMFloat -- TODO: generate the struct that we will return. + return $ LlvmFunctionDecl lbl link (llvmGhcCC dflags) retTy FixedArgs (map (toParams . getVarType) (llvmFunArgs dflags live)) (llvmFunAlign dflags) diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 43690e9..97042a6 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -126,12 +126,18 @@ stmtToInstrs stmt = case stmt of CmmUnsafeForeignCall target res args -> genCall target res args - -- Cmm call + -- Cmm tail call CmmCall { cml_target = arg, cml_args_regs = live, - cml_cont = maybeCont } -> case maybeCont of - Nothing -> genJump arg live -- Tail call - Just cont -> panic "todo: handle non-tail CmmCall" + cml_cont = Nothing } -> + genNativeCall Nothing arg live + + -- Cmm non-tail call + CmmCall { cml_target = arg, + cml_args_regs = live, + cml_cont = Just cont, + cml_args = argOffset } -> + genNativeCall (Just (cont, argOffset)) arg live _ -> panic "Llvm.CodeGen.stmtToInstrs" @@ -761,20 +767,24 @@ cmmPrimOpFunctions mop = do MO_AtomicWrite _ -> unsupported MO_Cmpxchg _ -> unsupported --- | Tail function calls -genJump :: CmmExpr -> [GlobalReg] -> LlvmM StmtData +-- | Native function calls. First arg indicates whether there is a continuation. +genNativeCall :: Maybe (Label, Int) -> CmmExpr -> [GlobalReg] -> LlvmM StmtData --- Call to known function -genJump (CmmLit (CmmLabel lbl)) live = do +-- Native call to a known function +genNativeCall maybeCont (CmmLit (CmmLabel lbl)) live = do (vf, stmts, top) <- getHsFunc live lbl (stgRegs, stgStmts) <- funEpilogue live - let s1 = Expr $ Call TailCall vf stgRegs llvmStdFunAttrs - let s2 = Return Nothing - return (stmts `appOL` stgStmts `snocOL` s1 `snocOL` s2, top) + let retTy = getRetTy $ getVarType vf + case maybeCont of + _ -> do -- native tail call + (retV, s1) <- doExpr retTy $ Call TailCall vf stgRegs llvmStdFunAttrs + let s2 = Return (Just retV) + return (stmts `appOL` stgStmts `snocOL` s1 `snocOL` s2, top) + -- Just (cont, offset) -> panic "kavon, handle non-tail known calls." --- Call to unknown function / address -genJump expr live = do +-- Tail call to unknown function / address. TODO: check if the expr is P64[Sp] to gen a ret. +genNativeCall _ expr live = do fty <- llvmFunTy live (vf, stmts, top) <- exprToVar expr dflags <- getDynFlags @@ -783,13 +793,14 @@ genJump expr live = do ty | isPointer ty -> LM_Bitcast ty | isInt ty -> LM_Inttoptr - ty -> panic $ "genJump: Expr is of bad type for function call! (" + ty -> panic $ "genNativeCall: Expr is of bad type for function call! (" ++ showSDoc dflags (ppr ty) ++ ")" (v1, s1) <- doExpr (pLift fty) $ Cast cast vf (pLift fty) (stgRegs, stgStmts) <- funEpilogue live - let s2 = Expr $ Call TailCall v1 stgRegs llvmStdFunAttrs - let s3 = Return Nothing + let retTy = getRetTy fty + (retV, s2) <- doExpr retTy $ Call TailCall v1 stgRegs llvmStdFunAttrs + let s3 = Return (Just retV) return (stmts `snocOL` s1 `appOL` stgStmts `snocOL` s2 `snocOL` s3, top) From git at git.haskell.org Tue Jun 27 09:15:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:07 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: add a todo for later (d3fe18c) Message-ID: <20170627091507.0E9B13A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/d3fe18c3cb9d3e73cb14f3698bd069177beed454/ghc >--------------------------------------------------------------- commit d3fe18c3cb9d3e73cb14f3698bd069177beed454 Author: Kavon Farvardin Date: Tue May 16 10:28:34 2017 +0100 add a todo for later >--------------------------------------------------------------- d3fe18c3cb9d3e73cb14f3698bd069177beed454 compiler/llvmGen/LlvmCodeGen/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index 46d01bf..a4b7f07 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -126,7 +126,7 @@ llvmFunSig' live lbl link dflags <- getDynFlags -- the standard set of argument types passed/returned. let stdConvention = map getVarType (llvmFunArgs dflags live) - let retTy = LMStructU $ stdConvention + let retTy = LMStructU $ stdConvention -- TODO: introduce a type alias to reduce bytes output return $ LlvmFunctionDecl lbl link (llvmGhcCC dflags) retTy FixedArgs (map toParams stdConvention) (llvmFunAlign dflags) From git at git.haskell.org Tue Jun 27 09:15:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:12 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: add todos to improve some things (6fa6a7e) Message-ID: <20170627091512.6AFE83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/6fa6a7ea8f4b5487aeaa71cbab1e83399e2300a7/ghc >--------------------------------------------------------------- commit 6fa6a7ea8f4b5487aeaa71cbab1e83399e2300a7 Author: Kavon Farvardin Date: Tue May 16 11:05:32 2017 +0100 add todos to improve some things >--------------------------------------------------------------- 6fa6a7ea8f4b5487aeaa71cbab1e83399e2300a7 compiler/llvmGen/LlvmCodeGen/Base.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index a4b7f07..7369cdb 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -121,12 +121,12 @@ llvmFunSig live lbl link = do llvmFunSig' :: LiveGlobalRegs -> LMString -> LlvmLinkageType -> LlvmM LlvmFunctionDecl llvmFunSig' live lbl link - = do let toParams x | isPointer x = (x, [NoAlias, NoCapture]) + = do let toParams x | isPointer x = (x, [NoAlias, NoCapture]) -- TODO(kavon): add NonNull | otherwise = (x, []) dflags <- getDynFlags -- the standard set of argument types passed/returned. let stdConvention = map getVarType (llvmFunArgs dflags live) - let retTy = LMStructU $ stdConvention -- TODO: introduce a type alias to reduce bytes output + let retTy = LMStructU $ stdConvention -- TODO(kavon): introduce a type alias to reduce bytes output return $ LlvmFunctionDecl lbl link (llvmGhcCC dflags) retTy FixedArgs (map toParams stdConvention) (llvmFunAlign dflags) From git at git.haskell.org Tue Jun 27 09:15:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:15 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: stopping here to upgrade CmmCall's information (8eb6125) Message-ID: <20170627091515.1D1103A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/8eb612516ea6386b1d98ebde2f0ffc8d2d1defe6/ghc >--------------------------------------------------------------- commit 8eb612516ea6386b1d98ebde2f0ffc8d2d1defe6 Author: Kavon Farvardin Date: Tue May 16 16:14:02 2017 +0100 stopping here to upgrade CmmCall's information >--------------------------------------------------------------- 8eb612516ea6386b1d98ebde2f0ffc8d2d1defe6 compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 18 ++++++++++++++++-- 1 file changed, 16 insertions(+), 2 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 97042a6..65e5a1f 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -776,12 +776,18 @@ genNativeCall maybeCont (CmmLit (CmmLabel lbl)) live = do (stgRegs, stgStmts) <- funEpilogue live let retTy = getRetTy $ getVarType vf case maybeCont of - _ -> do -- native tail call + -- tail call to a known fun + Nothing -> do (retV, s1) <- doExpr retTy $ Call TailCall vf stgRegs llvmStdFunAttrs let s2 = Return (Just retV) return (stmts `appOL` stgStmts `snocOL` s1 `snocOL` s2, top) - -- Just (cont, offset) -> panic "kavon, handle non-tail known calls." + -- non-tail call to a known fun + Just (cont, offset) -> do + -- TODO add metadata to this StdCall with the offset and label name + (retV, s1) <- doExpr retTy $ Call StdCall vf stgRegs llvmStdFunAttrs + endStms <- doReturnTo cont retV + return (stmts `appOL` stgStmts `snocOL` s1 `appOL` endStms, top) -- Tail call to unknown function / address. TODO: check if the expr is P64[Sp] to gen a ret. genNativeCall _ expr live = do @@ -804,6 +810,14 @@ genNativeCall _ expr live = do return (stmts `snocOL` s1 `appOL` stgStmts `snocOL` s2 `snocOL` s3, top) +doReturnTo :: Label -> LlvmVar -> LlvmM (OrdList LlvmStatement) +doReturnTo cont retV = panic "handleReturn" + -- TODO: we need to know the [GlobalReg] that are live in the continuation, + -- aka, what values did the call return? + -- todo: extract vals + -- todo store vals into reg allocas + -- emit a branch + -- | CmmAssign operation -- From git at git.haskell.org Tue Jun 27 09:15:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:09 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: fix ppr typo for readnone; added NonNull param attr (e655d2b) Message-ID: <20170627091509.B7D323A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/e655d2b8a0b556cb1ffe552c2f8fcf8e1cf0a7ec/ghc >--------------------------------------------------------------- commit e655d2b8a0b556cb1ffe552c2f8fcf8e1cf0a7ec Author: Kavon Farvardin Date: Tue May 16 11:05:02 2017 +0100 fix ppr typo for readnone; added NonNull param attr >--------------------------------------------------------------- e655d2b8a0b556cb1ffe552c2f8fcf8e1cf0a7ec compiler/llvmGen/Llvm/Types.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/compiler/llvmGen/Llvm/Types.hs b/compiler/llvmGen/Llvm/Types.hs index 6245642..a84446c 100644 --- a/compiler/llvmGen/Llvm/Types.hs +++ b/compiler/llvmGen/Llvm/Types.hs @@ -467,6 +467,9 @@ data LlvmParamAttr -- | This indicates that the pointer parameter can be excised using the -- trampoline intrinsics. | Nest + -- | This indicates that the parameter or return pointer is not null. + -- This attribute may only be applied to pointer typed parameters. + | NonNull deriving (Eq) instance Outputable LlvmParamAttr where @@ -478,6 +481,7 @@ instance Outputable LlvmParamAttr where ppr NoAlias = text "noalias" ppr NoCapture = text "nocapture" ppr Nest = text "nest" + ppr NonNull = text "nonnull" -- | Llvm Function Attributes. -- @@ -564,7 +568,7 @@ instance Outputable LlvmFuncAttr where ppr OptSize = text "optsize" ppr NoReturn = text "noreturn" ppr NoUnwind = text "nounwind" - ppr ReadNone = text "readnon" + ppr ReadNone = text "readnone" ppr ReadOnly = text "readonly" ppr Ssp = text "ssp" ppr SspReq = text "ssqreq" From git at git.haskell.org Tue Jun 27 09:15:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:17 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: in process of adding cml_ret_args field to CmmCall (6eae1eb) Message-ID: <20170627091517.CF7483A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/6eae1ebb6c908fd8d4495bb4b023861ae1694692/ghc >--------------------------------------------------------------- commit 6eae1ebb6c908fd8d4495bb4b023861ae1694692 Author: Kavon Farvardin Date: Tue May 16 16:49:14 2017 +0100 in process of adding cml_ret_args field to CmmCall >--------------------------------------------------------------- 6eae1ebb6c908fd8d4495bb4b023861ae1694692 compiler/cmm/CmmCommonBlockElim.hs | 5 +++-- compiler/cmm/CmmContFlowOpt.hs | 4 ++-- compiler/cmm/CmmNode.hs | 8 +++++++- compiler/cmm/CmmProcPoint.hs | 2 +- compiler/cmm/MkGraph.hs | 16 ++++++++-------- compiler/cmm/PprCmm.hs | 5 +++-- 6 files changed, 24 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 6eae1ebb6c908fd8d4495bb4b023861ae1694692 From git at git.haskell.org Tue Jun 27 09:15:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:20 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: CmmCall now keeps track of the returned global regs, which is information we were throwing away during codeGen (f6e6875) Message-ID: <20170627091520.920833A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/f6e687572a9add1c43e4bc8adb996a0113ad2d24/ghc >--------------------------------------------------------------- commit f6e687572a9add1c43e4bc8adb996a0113ad2d24 Author: Kavon Farvardin Date: Wed May 17 16:21:04 2017 +0100 CmmCall now keeps track of the returned global regs, which is information we were throwing away during codeGen >--------------------------------------------------------------- f6e687572a9add1c43e4bc8adb996a0113ad2d24 compiler/cmm/CmmLayoutStack.hs | 1 + compiler/cmm/MkGraph.hs | 10 ++++++---- compiler/cmm/PprCmm.hs | 2 +- compiler/codeGen/StgCmmExpr.hs | 12 ++++++------ compiler/codeGen/StgCmmForeign.hs | 2 +- compiler/codeGen/StgCmmHeap.hs | 18 +++++++++--------- compiler/codeGen/StgCmmLayout.hs | 6 +++--- compiler/codeGen/StgCmmMonad.hs | 6 +++--- 8 files changed, 30 insertions(+), 27 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 f6e687572a9add1c43e4bc8adb996a0113ad2d24 From git at git.haskell.org Tue Jun 27 09:15:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:23 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: working on doReturnTo; not much left in there (0bf8300) Message-ID: <20170627091523.4880B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/0bf83005a3df90869c97dabc078c4ff592ba6adc/ghc >--------------------------------------------------------------- commit 0bf83005a3df90869c97dabc078c4ff592ba6adc Author: Kavon Farvardin Date: Wed May 17 18:44:20 2017 +0100 working on doReturnTo; not much left in there >--------------------------------------------------------------- 0bf83005a3df90869c97dabc078c4ff592ba6adc compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 53 +++++++++++++++++++++++++-------- compiler/llvmGen/LlvmCodeGen/Regs.hs | 2 +- 2 files changed, 41 insertions(+), 14 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 65e5a1f..204f2ef 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -38,8 +38,9 @@ import Control.Monad.Trans.Writer import Data.Semigroup ( Semigroup ) import qualified Data.Semigroup as Semigroup #endif -import Data.List ( nub ) +import Data.List ( nub, mapAccumL ) import Data.Maybe ( catMaybes ) +import Control.Monad ( foldM ) type Atomic = Bool type LlvmStatements = OrdList LlvmStatement @@ -136,8 +137,9 @@ stmtToInstrs stmt = case stmt of CmmCall { cml_target = arg, cml_args_regs = live, cml_cont = Just cont, - cml_args = argOffset } -> - genNativeCall (Just (cont, argOffset)) arg live + cml_args = argOffset, + cml_ret_regs = retRegs } -> + genNativeCall (Just (cont, argOffset, retRegs)) arg live _ -> panic "Llvm.CodeGen.stmtToInstrs" @@ -767,8 +769,12 @@ cmmPrimOpFunctions mop = do MO_AtomicWrite _ -> unsupported MO_Cmpxchg _ -> unsupported + +-- block, arg byte off, return regs (not including Sp, etc) +type ContInfo = (Label, Int, [GlobalReg]) + -- | Native function calls. First arg indicates whether there is a continuation. -genNativeCall :: Maybe (Label, Int) -> CmmExpr -> [GlobalReg] -> LlvmM StmtData +genNativeCall :: Maybe ContInfo -> CmmExpr -> [GlobalReg] -> LlvmM StmtData -- Native call to a known function genNativeCall maybeCont (CmmLit (CmmLabel lbl)) live = do @@ -783,10 +789,10 @@ genNativeCall maybeCont (CmmLit (CmmLabel lbl)) live = do return (stmts `appOL` stgStmts `snocOL` s1 `snocOL` s2, top) -- non-tail call to a known fun - Just (cont, offset) -> do + Just contInfo -> do -- TODO add metadata to this StdCall with the offset and label name (retV, s1) <- doExpr retTy $ Call StdCall vf stgRegs llvmStdFunAttrs - endStms <- doReturnTo cont retV + endStms <- doReturnTo contInfo retV return (stmts `appOL` stgStmts `snocOL` s1 `appOL` endStms, top) -- Tail call to unknown function / address. TODO: check if the expr is P64[Sp] to gen a ret. @@ -810,13 +816,34 @@ genNativeCall _ expr live = do return (stmts `snocOL` s1 `appOL` stgStmts `snocOL` s2 `snocOL` s3, top) -doReturnTo :: Label -> LlvmVar -> LlvmM (OrdList LlvmStatement) -doReturnTo cont retV = panic "handleReturn" - -- TODO: we need to know the [GlobalReg] that are live in the continuation, - -- aka, what values did the call return? - -- todo: extract vals - -- todo store vals into reg allocas - -- emit a branch + +doReturnTo :: ContInfo -> LlvmVar -> LlvmM LlvmStatements +doReturnTo (retl, off, retRegs) llRetV = do + -- find the struct fields corresponding to each live register + -- according to the return convention. + platform <- getDynFlag targetPlatform + let regOrder = activeStgRegs platform + live = alwaysLive ++ retRegs + liveRegs = filter (\x -> x `elem` live) regOrder + withIdx i x = (i+1, (x, i)) + (_, retConv) = mapAccumL withIdx 0 liveRegs + + -- for each (GlobalReg, Int), we will add to the stms an extract + -- from llRetV followed by a store to the alloca backing the reg + extract stms (reg, i) = do + regAlloca <- getCmmReg $ CmmGlobal reg + let (LMPointer ty) = getVarType regAlloca + (newVal, s1) <- doExpr ty $ ExtractV llRetV i + let s2 = Store newVal regAlloca + return (stms `snocOL` s1 `snocOL` s2) + + -- extract the regs from the struct and update their allocas + updateStms <- foldM extract nilOL retConv + + -- TODO make a branch instr + + -- TODO combine all the LlvmStatements together and return them. + return updateStms -- | CmmAssign operation diff --git a/compiler/llvmGen/LlvmCodeGen/Regs.hs b/compiler/llvmGen/LlvmCodeGen/Regs.hs index e09ab80..539b2bb 100644 --- a/compiler/llvmGen/LlvmCodeGen/Regs.hs +++ b/compiler/llvmGen/LlvmCodeGen/Regs.hs @@ -103,7 +103,7 @@ stgTBAA , (heapN, fsLit "heap", Just topN) , (rxN, fsLit "rx", Just heapN) , (baseN, fsLit "base", Just topN) - -- FIX: Not 100% sure if this hierarchy is complete. I think the big thing + -- FIXME(kavon): Not 100% sure if this hierarchy is complete. I think the big thing -- is Sp is never aliased, so might want to change the hierarchy to have Sp -- on its own branch that is never aliased (e.g never use top as a TBAA -- node). From git at git.haskell.org Tue Jun 27 09:15:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:25 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: need to change what registers are alloca'd in the prologue (10f2860) Message-ID: <20170627091525.F22A53A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/10f28601a960fbaa569fa807014197735db020fe/ghc >--------------------------------------------------------------- commit 10f28601a960fbaa569fa807014197735db020fe Author: Kavon Farvardin Date: Thu May 18 12:19:45 2017 +0100 need to change what registers are alloca'd in the prologue >--------------------------------------------------------------- 10f28601a960fbaa569fa807014197735db020fe compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 42 ++++++++++++++++++--------------- 1 file changed, 23 insertions(+), 19 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 204f2ef..aa0baef 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -38,9 +38,9 @@ import Control.Monad.Trans.Writer import Data.Semigroup ( Semigroup ) import qualified Data.Semigroup as Semigroup #endif -import Data.List ( nub, mapAccumL ) +import Data.List ( nub ) import Data.Maybe ( catMaybes ) -import Control.Monad ( foldM ) +import Control.Monad ( foldM, filterM ) type Atomic = Bool type LlvmStatements = OrdList LlvmStatement @@ -818,32 +818,31 @@ genNativeCall _ expr live = do doReturnTo :: ContInfo -> LlvmVar -> LlvmM LlvmStatements -doReturnTo (retl, off, retRegs) llRetV = do +doReturnTo (retl, _, retRegs) llRetV = do -- find the struct fields corresponding to each live register -- according to the return convention. platform <- getDynFlag targetPlatform let regOrder = activeStgRegs platform - live = alwaysLive ++ retRegs - liveRegs = filter (\x -> x `elem` live) regOrder - withIdx i x = (i+1, (x, i)) - (_, retConv) = mapAccumL withIdx 0 liveRegs - - -- for each (GlobalReg, Int), we will add to the stms an extract - -- from llRetV followed by a store to the alloca backing the reg - extract stms (reg, i) = do + needsUpdate r = do + hasAlloca <- checkStackReg r + return (hasAlloca && (r `elem` alwaysLive || r `elem` retRegs)) + + -- liveRegs is ordered by the return convention. + liveRegs <- filterM needsUpdate regOrder + + -- for each reg, we will add to the stms an extract + -- from llRetV, followed by a store to the alloca backing the reg + let extract (i, stms) reg = do regAlloca <- getCmmReg $ CmmGlobal reg let (LMPointer ty) = getVarType regAlloca (newVal, s1) <- doExpr ty $ ExtractV llRetV i let s2 = Store newVal regAlloca - return (stms `snocOL` s1 `snocOL` s2) - - -- extract the regs from the struct and update their allocas - updateStms <- foldM extract nilOL retConv + return (i+1, stms `snocOL` s1 `snocOL` s2) - -- TODO make a branch instr - - -- TODO combine all the LlvmStatements together and return them. - return updateStms + -- update the allocas that correspond to the regs + (_, updateStms) <- foldM extract (0, nilOL) liveRegs + let br = Branch $ blockIdToLlvm retl + return (updateStms `snocOL` br) -- | CmmAssign operation @@ -1747,6 +1746,11 @@ genLit _ CmmHighStackMark -- question is never written. Therefore we skip it where we can to -- save a few lines in the output and hopefully speed compilation up a -- bit. +-- +-- FIXME(kavon): it seems inefficient to scan the whole function for reg assigns, +-- we could instead update a map of CmmRegs -> LlvmVars when we see assignments during +-- translation of a function's blocks, and then prepend the allocas to the entry block +-- once we're done. funPrologue :: LiveGlobalRegs -> [CmmBlock] -> LlvmM StmtData funPrologue live cmmBlocks = do From git at git.haskell.org Tue Jun 27 09:15:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:28 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: fixed up funPrologue and doReturnTo, though the latter produces verbose LLVM right now (6aab359) Message-ID: <20170627091528.A9B833A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/6aab3593333693d57ea38fe5fd58a4b7253adf67/ghc >--------------------------------------------------------------- commit 6aab3593333693d57ea38fe5fd58a4b7253adf67 Author: Kavon Farvardin Date: Thu May 18 15:08:13 2017 +0100 fixed up funPrologue and doReturnTo, though the latter produces verbose LLVM right now >--------------------------------------------------------------- 6aab3593333693d57ea38fe5fd58a4b7253adf67 compiler/llvmGen/LlvmCodeGen/Base.hs | 17 +++++++--- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 59 ++++++++++++++++++--------------- 2 files changed, 44 insertions(+), 32 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index 7369cdb..ac49c0c 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -26,7 +26,7 @@ module LlvmCodeGen.Base ( cmmToLlvmType, widthToLlvmFloat, widthToLlvmInt, llvmFunTy, llvmFunSig, llvmFunArgs, llvmStdFunAttrs, llvmFunAlign, llvmInfAlign, - llvmPtrBits, tysToParams, llvmFunSection, + llvmPtrBits, tysToParams, llvmFunSection, llvmStdConv, strCLabel_llvm, strDisplayName_llvm, strProcedureName_llvm, getGlobalPtr, generateExternDecls, @@ -145,10 +145,11 @@ llvmFunSection dflags lbl | gopt Opt_SplitSections dflags = Just (concatFS [fsLit ".text.", lbl]) | otherwise = Nothing --- | A Function's arguments -llvmFunArgs :: DynFlags -> LiveGlobalRegs -> [LlvmVar] -llvmFunArgs dflags live = - map (lmGlobalRegArg dflags) (filter isPassed (activeStgRegs platform)) +-- | The full set of Cmm registers passed to a function, in the correct order, +-- given the live argument registers. This is used for both call and return. +llvmStdConv :: DynFlags -> LiveGlobalRegs -> [GlobalReg] +llvmStdConv dflags live = + filter isPassed (activeStgRegs platform) where platform = targetPlatform dflags isLive r = not (isSSE r) || r `elem` alwaysLive || r `elem` live isPassed r = not (isSSE r) || isLive r @@ -159,6 +160,12 @@ llvmFunArgs dflags live = isSSE (ZmmReg _) = True isSSE _ = False +-- | A Function's arguments +llvmFunArgs :: DynFlags -> LiveGlobalRegs -> [LlvmVar] +llvmFunArgs dflags live = + map (lmGlobalRegArg dflags) (llvmStdConv dflags live) + + -- | Llvm standard fun attributes llvmStdFunAttrs :: [LlvmFuncAttr] llvmStdFunAttrs = [NoUnwind] diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index aa0baef..13f7258 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -40,7 +40,7 @@ import qualified Data.Semigroup as Semigroup #endif import Data.List ( nub ) import Data.Maybe ( catMaybes ) -import Control.Monad ( foldM, filterM ) +import Control.Monad ( foldM ) type Atomic = Bool type LlvmStatements = OrdList LlvmStatement @@ -818,29 +818,30 @@ genNativeCall _ expr live = do doReturnTo :: ContInfo -> LlvmVar -> LlvmM LlvmStatements -doReturnTo (retl, _, retRegs) llRetV = do - -- find the struct fields corresponding to each live register - -- according to the return convention. - platform <- getDynFlag targetPlatform - let regOrder = activeStgRegs platform - needsUpdate r = do - hasAlloca <- checkStackReg r - return (hasAlloca && (r `elem` alwaysLive || r `elem` retRegs)) - - -- liveRegs is ordered by the return convention. - liveRegs <- filterM needsUpdate regOrder - - -- for each reg, we will add to the stms an extract - -- from llRetV, followed by a store to the alloca backing the reg - let extract (i, stms) reg = do - regAlloca <- getCmmReg $ CmmGlobal reg - let (LMPointer ty) = getVarType regAlloca - (newVal, s1) <- doExpr ty $ ExtractV llRetV i - let s2 = Store newVal regAlloca - return (i+1, stms `snocOL` s1 `snocOL` s2) - - -- update the allocas that correspond to the regs - (_, updateStms) <- foldM extract (0, nilOL) liveRegs +doReturnTo (retl, _, retArgs) llRetV = do + dflags <- getDynFlags + let + -- TODO(kavon): seems retRegs includes all of the Rx registers + -- even if they are not live. LLVM will clean that up but it'd be nice if + -- we could avoid emitting those extracts by slimming down the retRegs list. + + -- retRegs is a subset of allRegs, with the _same relative ordering_ + retRegs = llvmStdConv dflags retArgs + allRegs = activeStgRegs $ targetPlatform dflags + + extract (z@(_, [], _)) _ = return z -- no more slots needed + extract (i, x:xs, stms) reg + | x /= reg = -- skip if x doesn't go in this slot + return (i+1, x:xs, stms) + | otherwise = do + regAlloca <- getCmmReg $ CmmGlobal reg + let (LMPointer ty) = getVarType regAlloca + (newVal, s1) <- doExpr ty $ ExtractV llRetV i + let s2 = Store newVal regAlloca + return (i+1, xs, stms `snocOL` s1 `snocOL` s2) + + -- update the allocas that correspond to the retRegs + (_, [], updateStms) <- foldM extract (0, retRegs, nilOL) allRegs let br = Branch $ blockIdToLlvm retl return (updateStms `snocOL` br) @@ -1753,7 +1754,7 @@ genLit _ CmmHighStackMark -- once we're done. funPrologue :: LiveGlobalRegs -> [CmmBlock] -> LlvmM StmtData funPrologue live cmmBlocks = do - + dflags <- getDynFlags trash <- getTrashRegs let getAssignedRegs :: CmmNode O O -> [CmmReg] getAssignedRegs (CmmAssign reg _) = [reg] @@ -1762,10 +1763,14 @@ funPrologue live cmmBlocks = do getAssignedRegs (CmmUnsafeForeignCall _ rs _) = map CmmGlobal trash ++ map CmmLocal rs getAssignedRegs _ = [] getRegsBlock (_, body, _) = concatMap getAssignedRegs $ blockToList body - assignedRegs = nub $ concatMap (getRegsBlock . blockSplit) cmmBlocks + + -- because we emit non-tail calls, the pinned registers such as the BasePtr is + -- returned and we need to use an alloca for it. -kavon + conventionRegs = map CmmGlobal $ llvmStdConv dflags live + + assignedRegs = nub $ concatMap (getRegsBlock . blockSplit) cmmBlocks ++ conventionRegs isLive r = r `elem` alwaysLive || r `elem` live - dflags <- getDynFlags stmtss <- flip mapM assignedRegs $ \reg -> case reg of CmmLocal (LocalReg un _) -> do From git at git.haskell.org Tue Jun 27 09:15:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:31 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: native calls are done (639178f) Message-ID: <20170627091531.6E8863A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/639178f62bae716a7369996d48d4341dcf68b8bc/ghc >--------------------------------------------------------------- commit 639178f62bae716a7369996d48d4341dcf68b8bc Author: Kavon Farvardin Date: Fri May 19 13:58:35 2017 +0100 native calls are done >--------------------------------------------------------------- 639178f62bae716a7369996d48d4341dcf68b8bc compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 58 ++++++++++++++++++++++++++------- 1 file changed, 47 insertions(+), 11 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 13f7258..506ed72 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -776,27 +776,32 @@ type ContInfo = (Label, Int, [GlobalReg]) -- | Native function calls. First arg indicates whether there is a continuation. genNativeCall :: Maybe ContInfo -> CmmExpr -> [GlobalReg] -> LlvmM StmtData +-- FIXME(kavon): the only difference I can see between these two cases is +-- whether we need to cast the function pointer or not. We could combine the +-- two cases of this function otherwise. + -- Native call to a known function genNativeCall maybeCont (CmmLit (CmmLabel lbl)) live = do + dflags <- getDynFlags (vf, stmts, top) <- getHsFunc live lbl (stgRegs, stgStmts) <- funEpilogue live let retTy = getRetTy $ getVarType vf + before = stmts `appOL` stgStmts case maybeCont of -- tail call to a known fun Nothing -> do (retV, s1) <- doExpr retTy $ Call TailCall vf stgRegs llvmStdFunAttrs let s2 = Return (Just retV) - return (stmts `appOL` stgStmts `snocOL` s1 `snocOL` s2, top) + return (before `snocOL` s1 `snocOL` s2, top) -- non-tail call to a known fun Just contInfo -> do - -- TODO add metadata to this StdCall with the offset and label name - (retV, s1) <- doExpr retTy $ Call StdCall vf stgRegs llvmStdFunAttrs - endStms <- doReturnTo contInfo retV - return (stmts `appOL` stgStmts `snocOL` s1 `appOL` endStms, top) + after <- mkNonTailCall dflags contInfo retTy vf stgRegs + return (before `appOL` after, top) + --- Tail call to unknown function / address. TODO: check if the expr is P64[Sp] to gen a ret. -genNativeCall _ expr live = do +-- Native call to unknown function / address. +genNativeCall maybeCont expr live = do fty <- llvmFunTy live (vf, stmts, top) <- exprToVar expr dflags <- getDynFlags @@ -811,10 +816,41 @@ genNativeCall _ expr live = do (v1, s1) <- doExpr (pLift fty) $ Cast cast vf (pLift fty) (stgRegs, stgStmts) <- funEpilogue live let retTy = getRetTy fty - (retV, s2) <- doExpr retTy $ Call TailCall v1 stgRegs llvmStdFunAttrs - let s3 = Return (Just retV) - return (stmts `snocOL` s1 `appOL` stgStmts `snocOL` s2 `snocOL` s3, - top) + before = stmts `snocOL` s1 `appOL` stgStmts + case maybeCont of + Nothing -> do + (retV, s2) <- doExpr retTy $ Call TailCall v1 stgRegs llvmStdFunAttrs + let s3 = Return (Just retV) + return (before `snocOL` s2 `snocOL` s3, + top) + Just contInfo -> do + after <- mkNonTailCall dflags contInfo retTy v1 stgRegs + return (before `appOL` after, top) + +mkNonTailCall :: DynFlags -> ContInfo -> LlvmType -> LlvmVar -> [LlvmVar] -> LlvmM LlvmStatements +mkNonTailCall dflags contInfo retTy vf stgRegs = do + (retV, callStm) <- doExpr retTy $ Call StdCall vf stgRegs llvmStdFunAttrs + let s1 = withReturnMeta dflags contInfo callStm + endStms <- doReturnTo contInfo retV + return $ s1 `consOL` endStms + +cps_retpt :: LMString +cps_retpt = fsLit "cps.retpt" + +withReturnMeta :: DynFlags -> ContInfo -> LlvmStatement -> LlvmStatement +withReturnMeta dflags (retl, argOff, _) stm = let + -- some unique name for the mangler corresponding to retl + name = MetaStr $ fsLit "todo" -- TODO(kavon) + + -- offset into the Sp where the return address should be written + wordBytes = widthInBytes $ wordWidth dflags + offInt = argOff - wordBytes + off = MetaStr $ mkFastString $ show offInt + + expr = MetaStruct [name, off] + in + MetaStmt [MetaAnnot cps_retpt expr] stm + doReturnTo :: ContInfo -> LlvmVar -> LlvmM LlvmStatements From git at git.haskell.org Tue Jun 27 09:15:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:34 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: doing some cleanup before using intrinsic (323bf7d) Message-ID: <20170627091534.267E63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/323bf7d17d262066b59701a3993d8cd7550af53f/ghc >--------------------------------------------------------------- commit 323bf7d17d262066b59701a3993d8cd7550af53f Author: Kavon Farvardin Date: Wed May 31 13:43:46 2017 +0100 doing some cleanup before using intrinsic >--------------------------------------------------------------- 323bf7d17d262066b59701a3993d8cd7550af53f compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 56 ++++++++++++++------------------- 1 file changed, 24 insertions(+), 32 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 506ed72..16add51 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -776,31 +776,13 @@ type ContInfo = (Label, Int, [GlobalReg]) -- | Native function calls. First arg indicates whether there is a continuation. genNativeCall :: Maybe ContInfo -> CmmExpr -> [GlobalReg] -> LlvmM StmtData --- FIXME(kavon): the only difference I can see between these two cases is --- whether we need to cast the function pointer or not. We could combine the --- two cases of this function otherwise. - --- Native call to a known function +-- Native call to a known Cmm function genNativeCall maybeCont (CmmLit (CmmLabel lbl)) live = do - dflags <- getDynFlags (vf, stmts, top) <- getHsFunc live lbl - (stgRegs, stgStmts) <- funEpilogue live - let retTy = getRetTy $ getVarType vf - before = stmts `appOL` stgStmts - case maybeCont of - -- tail call to a known fun - Nothing -> do - (retV, s1) <- doExpr retTy $ Call TailCall vf stgRegs llvmStdFunAttrs - let s2 = Return (Just retV) - return (before `snocOL` s1 `snocOL` s2, top) - - -- non-tail call to a known fun - Just contInfo -> do - after <- mkNonTailCall dflags contInfo retTy vf stgRegs - return (before `appOL` after, top) - + rest <- genNativeCall' maybeCont vf live + return (stmts `appOL` rest, top) --- Native call to unknown function / address. +-- Native call to unknown Cmm function / address. genNativeCall maybeCont expr live = do fty <- llvmFunTy live (vf, stmts, top) <- exprToVar expr @@ -814,18 +796,28 @@ genNativeCall maybeCont expr live = do ++ showSDoc dflags (ppr ty) ++ ")" (v1, s1) <- doExpr (pLift fty) $ Cast cast vf (pLift fty) + rest <- genNativeCall' maybeCont v1 live + return (stmts `snocOL` s1 `appOL` rest, top) + +-- now that we have the function we want to call as an LlvmVar, actually +-- build the statements needed to do so. +genNativeCall' :: Maybe ContInfo -> LlvmVar -> [GlobalReg] -> LlvmM LlvmStatements +genNativeCall' maybeCont fv live = do + dflags <- getDynFlags (stgRegs, stgStmts) <- funEpilogue live - let retTy = getRetTy fty - before = stmts `snocOL` s1 `appOL` stgStmts + let retTy = getRetTy $ getVarType fv case maybeCont of + -- tail call Nothing -> do - (retV, s2) <- doExpr retTy $ Call TailCall v1 stgRegs llvmStdFunAttrs - let s3 = Return (Just retV) - return (before `snocOL` s2 `snocOL` s3, - top) + (retV, s1) <- doExpr retTy $ Call TailCall fv stgRegs llvmStdFunAttrs + let s2 = Return (Just retV) + return (stgStmts `snocOL` s1 `snocOL` s2) + + -- non-tail call Just contInfo -> do - after <- mkNonTailCall dflags contInfo retTy v1 stgRegs - return (before `appOL` after, top) + ntCallStms <- mkNonTailCall dflags contInfo retTy fv stgRegs + return (stgStmts `appOL` ntCallStms) + mkNonTailCall :: DynFlags -> ContInfo -> LlvmType -> LlvmVar -> [LlvmVar] -> LlvmM LlvmStatements mkNonTailCall dflags contInfo retTy vf stgRegs = do @@ -839,8 +831,8 @@ cps_retpt = fsLit "cps.retpt" withReturnMeta :: DynFlags -> ContInfo -> LlvmStatement -> LlvmStatement withReturnMeta dflags (retl, argOff, _) stm = let - -- some unique name for the mangler corresponding to retl - name = MetaStr $ fsLit "todo" -- TODO(kavon) + -- TODO some unique name for the mangler corresponding to retl + name = MetaStr $ fsLit "todo" -- offset into the Sp where the return address should be written wordBytes = widthInBytes $ wordWidth dflags From git at git.haskell.org Tue Jun 27 09:15:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:36 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: need to add ppr support for CPSCall (1ae76b5) Message-ID: <20170627091536.D1CD33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/1ae76b5a3c829ccb8384eba57936df38cf00eb8d/ghc >--------------------------------------------------------------- commit 1ae76b5a3c829ccb8384eba57936df38cf00eb8d Author: Kavon Farvardin Date: Wed May 31 15:37:50 2017 +0100 need to add ppr support for CPSCall >--------------------------------------------------------------- 1ae76b5a3c829ccb8384eba57936df38cf00eb8d compiler/llvmGen/Llvm/Types.hs | 7 +++++++ compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 28 ++++++++++++++-------------- 2 files changed, 21 insertions(+), 14 deletions(-) diff --git a/compiler/llvmGen/Llvm/Types.hs b/compiler/llvmGen/Llvm/Types.hs index a84446c..8e04ed7 100644 --- a/compiler/llvmGen/Llvm/Types.hs +++ b/compiler/llvmGen/Llvm/Types.hs @@ -583,6 +583,13 @@ data LlvmCallType = StdCall -- | Tail call, perform the call in the current stack frame. | TailCall + -- | A non-tail call in continuation-passing style, + -- which is described with the intrinsic @llvm.experimental.cpscall + | CPSCall { + info_id :: Int64, -- an ID used by the mangler + ra_off :: Int32, -- byte offset from Sp for the return address + sp_argnum :: Int16 -- indicates the Sp arg passed to callee + } deriving (Eq,Show) -- | Different calling conventions a function can use. diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 16add51..6353355 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -38,7 +38,7 @@ import Control.Monad.Trans.Writer import Data.Semigroup ( Semigroup ) import qualified Data.Semigroup as Semigroup #endif -import Data.List ( nub ) +import Data.List ( nub, elemIndex ) import Data.Maybe ( catMaybes ) import Control.Monad ( foldM ) @@ -821,27 +821,27 @@ genNativeCall' maybeCont fv live = do mkNonTailCall :: DynFlags -> ContInfo -> LlvmType -> LlvmVar -> [LlvmVar] -> LlvmM LlvmStatements mkNonTailCall dflags contInfo retTy vf stgRegs = do - (retV, callStm) <- doExpr retTy $ Call StdCall vf stgRegs llvmStdFunAttrs - let s1 = withReturnMeta dflags contInfo callStm + let ct = getCallType dflags contInfo + (retV, callStm) <- doExpr retTy $ Call ct vf stgRegs llvmStdFunAttrs endStms <- doReturnTo contInfo retV - return $ s1 `consOL` endStms + return $ callStm `consOL` endStms -cps_retpt :: LMString -cps_retpt = fsLit "cps.retpt" -withReturnMeta :: DynFlags -> ContInfo -> LlvmStatement -> LlvmStatement -withReturnMeta dflags (retl, argOff, _) stm = let - -- TODO some unique name for the mangler corresponding to retl - name = MetaStr $ fsLit "todo" +getCallType :: DynFlags -> ContInfo -> LlvmCallType +getCallType dflags (retl, argOff, _) = let + -- mangler will look for this unique number + info64 = fromIntegral $ getKey $ getUnique retl -- offset into the Sp where the return address should be written wordBytes = widthInBytes $ wordWidth dflags - offInt = argOff - wordBytes - off = MetaStr $ mkFastString $ show offInt + ra32 = fromIntegral $ argOff - wordBytes - expr = MetaStruct [name, off] + -- get argument number of Sp in our calling convention + allRegs = activeStgRegs $ targetPlatform dflags + Just spArgnum = elemIndex Sp allRegs + argnum16 = fromIntegral spArgnum in - MetaStmt [MetaAnnot cps_retpt expr] stm + CPSCall {info_id = info64, ra_off = ra32, sp_argnum = argnum16} From git at git.haskell.org Tue Jun 27 09:15:39 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:39 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: doing some refactoring to add CPSCall pp (35acd14) Message-ID: <20170627091539.84E243A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/35acd142af52a201c71f151d03af4f5ad59468c6/ghc >--------------------------------------------------------------- commit 35acd142af52a201c71f151d03af4f5ad59468c6 Author: Kavon Farvardin Date: Wed May 31 16:27:24 2017 +0100 doing some refactoring to add CPSCall pp >--------------------------------------------------------------- 35acd142af52a201c71f151d03af4f5ad59468c6 compiler/llvmGen/Llvm/PpLlvm.hs | 35 +++++++++++++++++++---------------- 1 file changed, 19 insertions(+), 16 deletions(-) diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs index 5812340..c1dd9fd 100644 --- a/compiler/llvmGen/Llvm/PpLlvm.hs +++ b/compiler/llvmGen/Llvm/PpLlvm.hs @@ -251,30 +251,33 @@ ppLlvmExpression expr -- | Should always be a function pointer. So a global var of function type -- (since globals are always pointers) or a local var of pointer function type. ppCall :: LlvmCallType -> LlvmVar -> [MetaExpr] -> [LlvmFuncAttr] -> SDoc -ppCall ct fptr args attrs = case fptr of - -- - -- if local var function pointer, unwrap - LMLocalVar _ (LMPointer (LMFunction d)) -> ppCall' d - - -- should be function type otherwise - LMGlobalVar _ (LMFunction d) _ _ _ _ -> ppCall' d - - -- not pointer or function, so error - _other -> error $ "ppCall called with non LMFunction type!\nMust be " - ++ " called with either global var of function type or " - ++ "local var of pointer function type." +ppCall ct fptr args attrs = let + decl = getDecl fptr + in case ct of + TailCall -> ppRegularCall (text "tail ") decl + StdCall -> ppRegularCall empty decl + CPSCall {} -> panic "pp CPSCall pls" where - ppCall' (LlvmFunctionDecl _ _ cc ret argTy params _) = - let tc = if ct == TailCall then text "tail " else empty - ppValues = hsep $ punctuate comma $ map ppCallMetaExpr args + getDecl fptr = case fptr of + -- if local var function pointer, unwrap + LMLocalVar _ (LMPointer (LMFunction d)) -> d + -- should be function type otherwise + LMGlobalVar _ (LMFunction d) _ _ _ _ -> d + -- not pointer or function, so error + _other -> error $ "ppCall called with non LMFunction type!\nMust be " + ++ " called with either global var of function type or " + ++ "local var of pointer function type." + + ppRegularCall tailMarker (LlvmFunctionDecl _ _ cc ret argTy params _) = + let ppValues = hsep $ punctuate comma $ map ppCallMetaExpr args ppArgTy = (ppCommaJoin $ map fst params) <> (case argTy of VarArgs -> text ", ..." FixedArgs -> empty) fnty = space <> lparen <> ppArgTy <> rparen attrDoc = ppSpaceJoin attrs - in tc <> text "call" <+> ppr cc <+> ppr ret + in tailMarker <> text "call" <+> ppr cc <+> ppr ret <> fnty <+> ppName fptr <> lparen <+> ppValues <+> rparen <+> attrDoc From git at git.haskell.org Tue Jun 27 09:15:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:42 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: paused to work on paper (aac8ad9) Message-ID: <20170627091542.3D3613A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/aac8ad95bf1e60dade358a272ca942c8af7f4bcd/ghc >--------------------------------------------------------------- commit aac8ad95bf1e60dade358a272ca942c8af7f4bcd Author: Kavon Farvardin Date: Wed May 31 18:48:23 2017 +0100 paused to work on paper >--------------------------------------------------------------- aac8ad95bf1e60dade358a272ca942c8af7f4bcd compiler/llvmGen/Llvm/PpLlvm.hs | 24 +++++++++++++++--------- 1 file changed, 15 insertions(+), 9 deletions(-) diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs index c1dd9fd..2253d7d 100644 --- a/compiler/llvmGen/Llvm/PpLlvm.hs +++ b/compiler/llvmGen/Llvm/PpLlvm.hs @@ -269,16 +269,22 @@ ppCall ct fptr args attrs = let ++ " called with either global var of function type or " ++ "local var of pointer function type." - ppRegularCall tailMarker (LlvmFunctionDecl _ _ cc ret argTy params _) = - let ppValues = hsep $ punctuate comma $ map ppCallMetaExpr args - ppArgTy = (ppCommaJoin $ map fst params) <> - (case argTy of - VarArgs -> text ", ..." - FixedArgs -> empty) - fnty = space <> lparen <> ppArgTy <> rparen + ppRegularCall tailmrk (LlvmFunctionDecl _ _ cc ret argTy params _) = let + ppRet = ppr ret + ppFnName = ppName fptr + ppArgs = hsep $ punctuate comma $ map ppCallMetaExpr args + ppArgTys = (ppCommaJoin $ map fst params) <> + (case argTy of + VarArgs -> text ", ..." + FixedArgs -> empty) + in + ppCallWith tailmrk cc ppRet ppFnName ppArgTys ppArgs + + ppCallWith tailmrk cc ppRet ppFnName ppArgTys ppArgs = + let fnty = space <> lparen <> ppArgTys <> rparen attrDoc = ppSpaceJoin attrs - in tailMarker <> text "call" <+> ppr cc <+> ppr ret - <> fnty <+> ppName fptr <> lparen <+> ppValues + in tailmrk <> text "call" <+> ppr cc <+> ppRet + <> fnty <+> ppFnName <> lparen <+> ppArgs <+> rparen <+> attrDoc -- Metadata needs to be marked as having the `metadata` type when used From git at git.haskell.org Tue Jun 27 09:15:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:44 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: there's no need for so many spaces (c3300f7) Message-ID: <20170627091544.F261C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/c3300f7e336cf31ec8420760040e6ec08541e055/ghc >--------------------------------------------------------------- commit c3300f7e336cf31ec8420760040e6ec08541e055 Author: Kavon Farvardin Date: Thu Jun 1 12:20:56 2017 +0100 there's no need for so many spaces >--------------------------------------------------------------- c3300f7e336cf31ec8420760040e6ec08541e055 compiler/llvmGen/Llvm/Types.hs | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/compiler/llvmGen/Llvm/Types.hs b/compiler/llvmGen/Llvm/Types.hs index 8e04ed7..03c404d 100644 --- a/compiler/llvmGen/Llvm/Types.hs +++ b/compiler/llvmGen/Llvm/Types.hs @@ -70,8 +70,8 @@ instance Outputable LlvmType where ppr (LMVector nr tp ) = char '<' <> ppr nr <> text " x " <> ppr tp <> char '>' ppr (LMLabel ) = text "label" ppr (LMVoid ) = text "void" - ppr (LMStruct tys ) = text "<{" <> ppCommaJoin tys <> text "}>" - ppr (LMStructU tys ) = text "{" <> ppCommaJoin tys <> text "}" + ppr (LMStruct tys ) = text "<{" <> ppSlimCommaJoin tys <> text "}>" + ppr (LMStructU tys ) = text "{" <> ppSlimCommaJoin tys <> text "}" ppr (LMMetadata ) = text "metadata" ppr (LMFunction (LlvmFunctionDecl _ _ _ r varg p _)) @@ -83,11 +83,11 @@ ppParams :: LlvmParameterListType -> [LlvmParameter] -> SDoc ppParams varg p = let varg' = case varg of VarArgs | null args -> sLit "..." - | otherwise -> sLit ", ..." + | otherwise -> sLit ",..." _otherwise -> sLit "" -- by default we don't print param attributes args = map fst p - in ppCommaJoin args <> ptext varg' + in ppSlimCommaJoin args <> ptext varg' -- | An LLVM section definition. If Nothing then let LLVM decide the section type LMSection = Maybe LMString @@ -896,6 +896,10 @@ fixEndian = reverse -- * Misc functions -------------------------------------------------------------------------------- +-- no spaces version of CommaJoin +ppSlimCommaJoin :: (Outputable a) => [a] -> SDoc +ppSlimCommaJoin strs = hcat $ punctuate comma (map ppr strs) + ppCommaJoin :: (Outputable a) => [a] -> SDoc ppCommaJoin strs = hsep $ punctuate comma (map ppr strs) From git at git.haskell.org Tue Jun 27 09:15:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:47 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: implemented pprCPSCall.. need to print intrinsic in module now (8edde59) Message-ID: <20170627091547.AB5393A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/8edde590a371853e5bb3f8525547e6ab20efa2a9/ghc >--------------------------------------------------------------- commit 8edde590a371853e5bb3f8525547e6ab20efa2a9 Author: Kavon Farvardin Date: Thu Jun 1 13:42:51 2017 +0100 implemented pprCPSCall.. need to print intrinsic in module now >--------------------------------------------------------------- 8edde590a371853e5bb3f8525547e6ab20efa2a9 compiler/llvmGen/Llvm/PpLlvm.hs | 82 ++++++++++++++++++++++++++++++++--------- 1 file changed, 64 insertions(+), 18 deletions(-) diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs index 2253d7d..f7edef3 100644 --- a/compiler/llvmGen/Llvm/PpLlvm.hs +++ b/compiler/llvmGen/Llvm/PpLlvm.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP #-} +{-# LANGUAGE CPP, NamedFieldPuns #-} -------------------------------------------------------------------------------- -- | Pretty print LLVM IR Code. @@ -30,6 +30,7 @@ import Llvm.MetaData import Llvm.Types import Data.List ( intersperse ) +import Data.Bits ( finiteBitSize ) import Outputable import Unique import FastString ( sLit ) @@ -256,7 +257,7 @@ ppCall ct fptr args attrs = let in case ct of TailCall -> ppRegularCall (text "tail ") decl StdCall -> ppRegularCall empty decl - CPSCall {} -> panic "pp CPSCall pls" + (x at CPSCall {}) -> ppCPSCall x decl where getDecl fptr = case fptr of @@ -269,23 +270,68 @@ ppCall ct fptr args attrs = let ++ " called with either global var of function type or " ++ "local var of pointer function type." - ppRegularCall tailmrk (LlvmFunctionDecl _ _ cc ret argTy params _) = let - ppRet = ppr ret - ppFnName = ppName fptr - ppArgs = hsep $ punctuate comma $ map ppCallMetaExpr args - ppArgTys = (ppCommaJoin $ map fst params) <> - (case argTy of - VarArgs -> text ", ..." - FixedArgs -> empty) + ppRegularCall tailMark (LlvmFunctionDecl _ _ cc ret argTy params _) = let + ppArgTys = mkArgTys argTy params + ppFnTy = joinFnTy (ppr ret) ppArgTys in - ppCallWith tailmrk cc ppRet ppFnName ppArgTys ppArgs - - ppCallWith tailmrk cc ppRet ppFnName ppArgTys ppArgs = - let fnty = space <> lparen <> ppArgTys <> rparen - attrDoc = ppSpaceJoin attrs - in tailmrk <> text "call" <+> ppr cc <+> ppRet - <> fnty <+> ppFnName <> lparen <+> ppArgs - <+> rparen <+> attrDoc + joinCall tailMark cc ppFnTy ppFnName ppArgs + + ppCPSCall (CPSCall{info_id, ra_off, sp_argnum}) + (LlvmFunctionDecl _ _ cc ret argTy params _) = let + + md = [cvt info_id, cvt ra_off, cvt sp_argnum] + + retTy = ppr ret + calleeTy = (joinFnTy retTy $ mkArgTys argTy params) <> text "*" + + intArgTys = calleeTy <> comma <> + (hcat $ map printTy md) <> + text "..." + + intTy = joinFnTy retTy intArgTys + -- NB if there's a possibility of the callees having + -- different types, you'll want to place the mangled + -- type name here instead of "x". At the moment this + -- does not occur + intName = text "@llvm.experimental.cpscall.x" + + intArgs = calleeTy <+> ppFnName <> comma <+> + (hcat $ map printUse md) <> + ppArgs + + in + joinCall empty cc intTy intName intArgs + + ppCPSCall _ _ = panic "ppCPSCall: unexpected" + + + ppFnName = ppName fptr + ppArgs = hsep $ punctuate comma $ map ppCallMetaExpr args + + -- helper funs + + cvt i = (ppr $ LMInt $ finiteBitSize i, text $ show i) + printTy (ty, _) = ty <> comma + printUse (ty, val) = ty <+> val <> text ", " + + mkArgTys argTy params = + (ppSlimCommaJoin $ map fst params) <> + (case argTy of + VarArgs -> text ",..." + FixedArgs -> empty) + + joinFnTy ppRetTy ppArgTys = + ppRetTy <+> lparen <> ppArgTys <> rparen + + joinCall ppTail conv ppFnTy ppFn ppArgs = + let attrDoc = ppSpaceJoin attrs + in ppTail + <> text "call" + <+> ppr conv + <+> ppFnTy + <+> ppFn <> lparen + <> ppArgs + <> rparen <+> attrDoc -- Metadata needs to be marked as having the `metadata` type when used -- in a call argument From git at git.haskell.org Tue Jun 27 09:15:50 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:50 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: reverting llvm ppr (633284a) Message-ID: <20170627091550.5F9E03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/633284a841a188cbdad0beb8d797d6b4115e5e1b/ghc >--------------------------------------------------------------- commit 633284a841a188cbdad0beb8d797d6b4115e5e1b Author: Kavon Farvardin Date: Thu Jun 1 16:17:59 2017 +0100 reverting llvm ppr >--------------------------------------------------------------- 633284a841a188cbdad0beb8d797d6b4115e5e1b compiler/llvmGen/Llvm/PpLlvm.hs | 105 ++++++++++------------------------------ 1 file changed, 25 insertions(+), 80 deletions(-) diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs index f7edef3..5812340 100644 --- a/compiler/llvmGen/Llvm/PpLlvm.hs +++ b/compiler/llvmGen/Llvm/PpLlvm.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, NamedFieldPuns #-} +{-# LANGUAGE CPP #-} -------------------------------------------------------------------------------- -- | Pretty print LLVM IR Code. @@ -30,7 +30,6 @@ import Llvm.MetaData import Llvm.Types import Data.List ( intersperse ) -import Data.Bits ( finiteBitSize ) import Outputable import Unique import FastString ( sLit ) @@ -252,86 +251,32 @@ ppLlvmExpression expr -- | Should always be a function pointer. So a global var of function type -- (since globals are always pointers) or a local var of pointer function type. ppCall :: LlvmCallType -> LlvmVar -> [MetaExpr] -> [LlvmFuncAttr] -> SDoc -ppCall ct fptr args attrs = let - decl = getDecl fptr - in case ct of - TailCall -> ppRegularCall (text "tail ") decl - StdCall -> ppRegularCall empty decl - (x at CPSCall {}) -> ppCPSCall x decl +ppCall ct fptr args attrs = case fptr of + -- + -- if local var function pointer, unwrap + LMLocalVar _ (LMPointer (LMFunction d)) -> ppCall' d + + -- should be function type otherwise + LMGlobalVar _ (LMFunction d) _ _ _ _ -> ppCall' d + + -- not pointer or function, so error + _other -> error $ "ppCall called with non LMFunction type!\nMust be " + ++ " called with either global var of function type or " + ++ "local var of pointer function type." where - getDecl fptr = case fptr of - -- if local var function pointer, unwrap - LMLocalVar _ (LMPointer (LMFunction d)) -> d - -- should be function type otherwise - LMGlobalVar _ (LMFunction d) _ _ _ _ -> d - -- not pointer or function, so error - _other -> error $ "ppCall called with non LMFunction type!\nMust be " - ++ " called with either global var of function type or " - ++ "local var of pointer function type." - - ppRegularCall tailMark (LlvmFunctionDecl _ _ cc ret argTy params _) = let - ppArgTys = mkArgTys argTy params - ppFnTy = joinFnTy (ppr ret) ppArgTys - in - joinCall tailMark cc ppFnTy ppFnName ppArgs - - ppCPSCall (CPSCall{info_id, ra_off, sp_argnum}) - (LlvmFunctionDecl _ _ cc ret argTy params _) = let - - md = [cvt info_id, cvt ra_off, cvt sp_argnum] - - retTy = ppr ret - calleeTy = (joinFnTy retTy $ mkArgTys argTy params) <> text "*" - - intArgTys = calleeTy <> comma <> - (hcat $ map printTy md) <> - text "..." - - intTy = joinFnTy retTy intArgTys - -- NB if there's a possibility of the callees having - -- different types, you'll want to place the mangled - -- type name here instead of "x". At the moment this - -- does not occur - intName = text "@llvm.experimental.cpscall.x" - - intArgs = calleeTy <+> ppFnName <> comma <+> - (hcat $ map printUse md) <> - ppArgs - - in - joinCall empty cc intTy intName intArgs - - ppCPSCall _ _ = panic "ppCPSCall: unexpected" - - - ppFnName = ppName fptr - ppArgs = hsep $ punctuate comma $ map ppCallMetaExpr args - - -- helper funs - - cvt i = (ppr $ LMInt $ finiteBitSize i, text $ show i) - printTy (ty, _) = ty <> comma - printUse (ty, val) = ty <+> val <> text ", " - - mkArgTys argTy params = - (ppSlimCommaJoin $ map fst params) <> - (case argTy of - VarArgs -> text ",..." - FixedArgs -> empty) - - joinFnTy ppRetTy ppArgTys = - ppRetTy <+> lparen <> ppArgTys <> rparen - - joinCall ppTail conv ppFnTy ppFn ppArgs = - let attrDoc = ppSpaceJoin attrs - in ppTail - <> text "call" - <+> ppr conv - <+> ppFnTy - <+> ppFn <> lparen - <> ppArgs - <> rparen <+> attrDoc + ppCall' (LlvmFunctionDecl _ _ cc ret argTy params _) = + let tc = if ct == TailCall then text "tail " else empty + ppValues = hsep $ punctuate comma $ map ppCallMetaExpr args + ppArgTy = (ppCommaJoin $ map fst params) <> + (case argTy of + VarArgs -> text ", ..." + FixedArgs -> empty) + fnty = space <> lparen <> ppArgTy <> rparen + attrDoc = ppSpaceJoin attrs + in tc <> text "call" <+> ppr cc <+> ppr ret + <> fnty <+> ppName fptr <> lparen <+> ppValues + <+> rparen <+> attrDoc -- Metadata needs to be marked as having the `metadata` type when used -- in a call argument From git at git.haskell.org Tue Jun 27 09:15:53 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:53 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: less spaces so its more readable and less bytes (0925923) Message-ID: <20170627091553.15E253A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/09259235df5112b6dc0a04ac1a588570962c059f/ghc >--------------------------------------------------------------- commit 09259235df5112b6dc0a04ac1a588570962c059f Author: Kavon Farvardin Date: Thu Jun 1 16:21:42 2017 +0100 less spaces so its more readable and less bytes >--------------------------------------------------------------- 09259235df5112b6dc0a04ac1a588570962c059f compiler/llvmGen/Llvm/PpLlvm.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs index 5812340..ab95aed 100644 --- a/compiler/llvmGen/Llvm/PpLlvm.hs +++ b/compiler/llvmGen/Llvm/PpLlvm.hs @@ -268,9 +268,9 @@ ppCall ct fptr args attrs = case fptr of ppCall' (LlvmFunctionDecl _ _ cc ret argTy params _) = let tc = if ct == TailCall then text "tail " else empty ppValues = hsep $ punctuate comma $ map ppCallMetaExpr args - ppArgTy = (ppCommaJoin $ map fst params) <> + ppArgTy = (ppSlimCommaJoin $ map fst params) <> (case argTy of - VarArgs -> text ", ..." + VarArgs -> text ",..." FixedArgs -> empty) fnty = space <> lparen <> ppArgTy <> rparen attrDoc = ppSpaceJoin attrs From git at git.haskell.org Tue Jun 27 09:15:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:55 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: now properly using cpscall intrinsic. need to update mangler next (5378d06) Message-ID: <20170627091555.BF3D73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/5378d06eb75acabd0fec5fe3a72b1dfa7732ec9e/ghc >--------------------------------------------------------------- commit 5378d06eb75acabd0fec5fe3a72b1dfa7732ec9e Author: Kavon Farvardin Date: Thu Jun 1 16:23:44 2017 +0100 now properly using cpscall intrinsic. need to update mangler next >--------------------------------------------------------------- 5378d06eb75acabd0fec5fe3a72b1dfa7732ec9e compiler/llvmGen/Llvm/Types.hs | 7 ----- compiler/llvmGen/LlvmCodeGen/Base.hs | 17 +++++++++++- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 47 ++++++++++++++++++++------------- 3 files changed, 45 insertions(+), 26 deletions(-) diff --git a/compiler/llvmGen/Llvm/Types.hs b/compiler/llvmGen/Llvm/Types.hs index 03c404d..45c68af 100644 --- a/compiler/llvmGen/Llvm/Types.hs +++ b/compiler/llvmGen/Llvm/Types.hs @@ -583,13 +583,6 @@ data LlvmCallType = StdCall -- | Tail call, perform the call in the current stack frame. | TailCall - -- | A non-tail call in continuation-passing style, - -- which is described with the intrinsic @llvm.experimental.cpscall - | CPSCall { - info_id :: Int64, -- an ID used by the mangler - ra_off :: Int32, -- byte offset from Sp for the return address - sp_argnum :: Int16 -- indicates the Sp arg passed to callee - } deriving (Eq,Show) -- | Different calling conventions a function can use. diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index ac49c0c..47db6c4 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -31,7 +31,7 @@ module LlvmCodeGen.Base ( strCLabel_llvm, strDisplayName_llvm, strProcedureName_llvm, getGlobalPtr, generateExternDecls, - aliasify, + aliasify, cpsCallOf, ) where #include "HsVersions.h" @@ -501,6 +501,21 @@ aliasify (LMGlobal var val) = do , LMGlobal aliasVar (Just aliasVal) ] +cpsCallOf :: LlvmType -> LlvmType +cpsCallOf givenFn = LMFunction $ + LlvmFunctionDecl { + -- NB skipping type mangling because of current assumptions + decName = fsLit "llvm.experimental.cpscall.x", + funcLinkage = ExternallyVisible, + funcCc = CC_Ghc, + decReturnType = getRetTy givenFn, + decVarargs = VarArgs, + decParams = map noAttr [givenFn, i64, i32, i16], + funcAlign = Nothing + } + where + noAttr ty = (ty, []) + -- Note [Llvm Forward References] -- -- The issue here is that LLVM insists on being strongly typed at diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 6353355..4b8d4ae 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -779,8 +779,8 @@ genNativeCall :: Maybe ContInfo -> CmmExpr -> [GlobalReg] -> LlvmM StmtData -- Native call to a known Cmm function genNativeCall maybeCont (CmmLit (CmmLabel lbl)) live = do (vf, stmts, top) <- getHsFunc live lbl - rest <- genNativeCall' maybeCont vf live - return (stmts `appOL` rest, top) + (rest, top2) <- genNativeCall' maybeCont vf live + return (stmts `appOL` rest, top ++ top2) -- Native call to unknown Cmm function / address. genNativeCall maybeCont expr live = do @@ -796,12 +796,12 @@ genNativeCall maybeCont expr live = do ++ showSDoc dflags (ppr ty) ++ ")" (v1, s1) <- doExpr (pLift fty) $ Cast cast vf (pLift fty) - rest <- genNativeCall' maybeCont v1 live - return (stmts `snocOL` s1 `appOL` rest, top) + (rest, top2) <- genNativeCall' maybeCont v1 live + return (stmts `snocOL` s1 `appOL` rest, top ++ top2) -- now that we have the function we want to call as an LlvmVar, actually -- build the statements needed to do so. -genNativeCall' :: Maybe ContInfo -> LlvmVar -> [GlobalReg] -> LlvmM LlvmStatements +genNativeCall' :: Maybe ContInfo -> LlvmVar -> [GlobalReg] -> LlvmM StmtData genNativeCall' maybeCont fv live = do dflags <- getDynFlags (stgRegs, stgStmts) <- funEpilogue live @@ -811,37 +811,48 @@ genNativeCall' maybeCont fv live = do Nothing -> do (retV, s1) <- doExpr retTy $ Call TailCall fv stgRegs llvmStdFunAttrs let s2 = Return (Just retV) - return (stgStmts `snocOL` s1 `snocOL` s2) + return (stgStmts `snocOL` s1 `snocOL` s2, []) -- non-tail call Just contInfo -> do - ntCallStms <- mkNonTailCall dflags contInfo retTy fv stgRegs - return (stgStmts `appOL` ntCallStms) + (ntCallStms, top) <- mkNonTailCall dflags contInfo retTy fv stgRegs + return (stgStmts `appOL` ntCallStms, top) -mkNonTailCall :: DynFlags -> ContInfo -> LlvmType -> LlvmVar -> [LlvmVar] -> LlvmM LlvmStatements +mkNonTailCall :: DynFlags -> ContInfo -> LlvmType -> LlvmVar -> [LlvmVar] -> LlvmM StmtData mkNonTailCall dflags contInfo retTy vf stgRegs = do - let ct = getCallType dflags contInfo - (retV, callStm) <- doExpr retTy $ Call ct vf stgRegs llvmStdFunAttrs + -- fetch the intrinsic. + let cpscallTy @ (LMFunction decl) = cpsCallOf $ getVarType vf + (intFun, intStm, top) <- getInstrinct2 (decName decl) cpscallTy + + -- collect the args to the intrinsic + let consts = cpsCallConsts dflags contInfo + args = vf : consts ++ stgRegs + + (retV, callStm) <- doExpr retTy $ Call StdCall intFun args llvmStdFunAttrs endStms <- doReturnTo contInfo retV - return $ callStm `consOL` endStms + return (intStm `snocOL` callStm `appOL` endStms, top) -getCallType :: DynFlags -> ContInfo -> LlvmCallType -getCallType dflags (retl, argOff, _) = let +cpsCallConsts :: DynFlags -> ContInfo -> [LlvmVar] +cpsCallConsts dflags (retl, argOff, _) = let -- mangler will look for this unique number - info64 = fromIntegral $ getKey $ getUnique retl + info64 = toInteger $ getKey $ getUnique retl -- offset into the Sp where the return address should be written wordBytes = widthInBytes $ wordWidth dflags - ra32 = fromIntegral $ argOff - wordBytes + ra32 = toInteger $ argOff - wordBytes -- get argument number of Sp in our calling convention allRegs = activeStgRegs $ targetPlatform dflags Just spArgnum = elemIndex Sp allRegs - argnum16 = fromIntegral spArgnum + argnum16 = toInteger spArgnum + + mk ty val = LMLitVar $ LMIntLit val ty in - CPSCall {info_id = info64, ra_off = ra32, sp_argnum = argnum16} + [mk i64 info64, + mk i32 ra32, + mk i16 argnum16] From git at git.haskell.org Tue Jun 27 09:15:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:15:58 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: working on threading ManglerInfo to the LlvmMangler (7d52faa) Message-ID: <20170627091558.7D7143A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/7d52faa130d692c7e92b2e0b8f000a6bbb6b9b0d/ghc >--------------------------------------------------------------- commit 7d52faa130d692c7e92b2e0b8f000a6bbb6b9b0d Author: Kavon Farvardin Date: Fri Jun 2 18:49:41 2017 +0100 working on threading ManglerInfo to the LlvmMangler >--------------------------------------------------------------- 7d52faa130d692c7e92b2e0b8f000a6bbb6b9b0d compiler/cmm/Cmm.hs | 4 ++-- compiler/ghc.mk | 45 +++++++++++++++++++++++++++++------------ compiler/main/CodeOutput.hs | 32 ++++++++++++++++------------- compiler/main/DriverPhases.hs | 1 - compiler/main/DriverPipeline.hs | 11 +++++++--- compiler/main/HscMain.hs | 6 +++--- compiler/main/PipelineMonad.hs | 3 +++ 7 files changed, 66 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 7d52faa130d692c7e92b2e0b8f000a6bbb6b9b0d From git at git.haskell.org Tue Jun 27 09:16:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:01 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: mangInfo is at the LlvmMangler phase, now need to send some (2013b25) Message-ID: <20170627091601.316353A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/2013b25f6040384b62fb5b6297f49d4d44ca69d5/ghc >--------------------------------------------------------------- commit 2013b25f6040384b62fb5b6297f49d4d44ca69d5 Author: Kavon Farvardin Date: Mon Jun 5 11:13:44 2017 +0100 mangInfo is at the LlvmMangler phase, now need to send some >--------------------------------------------------------------- 2013b25f6040384b62fb5b6297f49d4d44ca69d5 compiler/main/DriverPipeline.hs | 30 ++++++++++++++++++++++-------- 1 file changed, 22 insertions(+), 8 deletions(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index d32f185..3c670fe 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1079,7 +1079,11 @@ runPhase (HscOut src_flavour mod_name result) _ dflags = do mapM (uncurry (compileForeign hsc_env')) foreign_files setForeignOs (maybe [] return stub_o ++ foreign_os) - return (RealPhase next_phase, outputFilename) + let kind = case next_phase of + LlvmOpt -> RealPhaseWithInfo + _ -> \ _ p -> RealPhase p + + return (kind mangInfo next_phase, outputFilename) ----------------------------------------------------------------------------- -- Cmm phase @@ -1417,7 +1421,7 @@ runPhase (RealPhase SplitAs) _input_fn dflags ----------------------------------------------------------------------------- -- LlvmOpt phase -runPhase (RealPhase LlvmOpt) input_fn dflags +runPhase (RealPhaseWithInfo mangInfo LlvmOpt) input_fn dflags = do let opt_lvl = max 0 (min 2 $ optLevel dflags) -- don't specify anything if user has specified commands. We do this @@ -1440,7 +1444,7 @@ runPhase (RealPhase LlvmOpt) input_fn dflags ++ optFlag ++ [SysTools.Option tbaa]) - return (RealPhase LlvmLlc, output_fn) + return (RealPhaseWithInfo mangInfo LlvmLlc, output_fn) where -- we always (unless -optlo specified) run Opt since we rely on it to -- fix up some pretty big deficiencies in the code we generate @@ -1452,7 +1456,7 @@ runPhase (RealPhase LlvmOpt) input_fn dflags ----------------------------------------------------------------------------- -- LlvmLlc phase -runPhase (RealPhase LlvmLlc) input_fn dflags +runPhase (RealPhaseWithInfo mangInfo LlvmLlc) input_fn dflags = do let opt_lvl = max 0 (min 2 $ optLevel dflags) -- iOS requires external references to be loaded indirectly from the @@ -1485,7 +1489,15 @@ runPhase (RealPhase LlvmLlc) input_fn dflags ++ map SysTools.Option avx512Opts ++ map SysTools.Option stackAlignOpts) - return (RealPhase next_phase, output_fn) + let doNext = case (next_phase, mangInfo) of + (LlvmMangle, i) -> RealPhaseWithInfo i LlvmMangle + (_, Just _) -> panic ("after LLC: TNTC info was provided, " + ++ "but -dno-llvm-mangler was given!") + -- TODO(kavon) probably should just be + -- a warning since its a debug flag anyways + (p, Nothing) -> RealPhase p + + return (doNext, output_fn) where -- Bug in LLVM at O3 on OSX. llvmOpts = if platformOS (targetPlatform dflags) == OSDarwin @@ -1535,13 +1547,15 @@ runPhase (RealPhase LlvmLlc) input_fn dflags ----------------------------------------------------------------------------- -- LlvmMangle phase -runPhase (RealPhase LlvmMangle) input_fn dflags +runPhase (RealPhaseWithInfo (Just info) LlvmMangle) input_fn dflags = do let next_phase = if gopt Opt_SplitObjs dflags then Splitter else As False output_fn <- phaseOutputFilename next_phase liftIO $ llvmFixupAsm dflags input_fn output_fn return (RealPhase next_phase, output_fn) +runPhase (RealPhaseWithInfo Nothing LlvmMangle) _ _ = panic "phase LlvmMangle needs info!" + ----------------------------------------------------------------------------- -- merge in stub objects @@ -1558,10 +1572,10 @@ runPhase (RealPhase MergeForeign) input_fn dflags -- warning suppression runPhase (RealPhase other) _input_fn _dflags = - panic ("runPhase: don't know how to run phase " ++ show other) + panic ("runPhase: don't know how to run phase: " ++ show other) runPhase (RealPhaseWithInfo _ other) _input_fn _dflags = - panic ("runPhase: don't know how to run phase (with info) " ++ show other) + panic ("runPhase: don't know how to run phase (with mangler info): " ++ show other) maybeMergeForeign :: CompPipeline Phase maybeMergeForeign From git at git.haskell.org Tue Jun 27 09:16:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:03 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: did that todo (d15cecc) Message-ID: <20170627091603.DC2C03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/d15cecc271709f9d5c22464c173061b42eb2857d/ghc >--------------------------------------------------------------- commit d15cecc271709f9d5c22464c173061b42eb2857d Author: Kavon Farvardin Date: Mon Jun 5 11:29:29 2017 +0100 did that todo >--------------------------------------------------------------- d15cecc271709f9d5c22464c173061b42eb2857d compiler/main/DriverPipeline.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 3c670fe..2a94105 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1072,7 +1072,7 @@ runPhase (HscOut src_flavour mod_name result) _ dflags = do PipeState{hsc_env=hsc_env'} <- getPipeState - (outputFilename, mStub, foreign_files, mangInfo) <- liftIO $ -- TODO(kavon) use mangInfo + (outputFilename, mStub, foreign_files, mangInfo) <- liftIO $ hscGenHardCode hsc_env' cgguts mod_summary output_fn stub_o <- liftIO (mapM (compileStub hsc_env') mStub) foreign_os <- liftIO $ From git at git.haskell.org Tue Jun 27 09:16:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:06 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: now just need to have mangler use the map (1c3e024) Message-ID: <20170627091606.927BB3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/1c3e024eaf3ebcfe1c7fecece265ea4fffdcb292/ghc >--------------------------------------------------------------- commit 1c3e024eaf3ebcfe1c7fecece265ea4fffdcb292 Author: Kavon Farvardin Date: Mon Jun 5 14:45:26 2017 +0100 now just need to have mangler use the map >--------------------------------------------------------------- 1c3e024eaf3ebcfe1c7fecece265ea4fffdcb292 compiler/llvmGen/LlvmCodeGen.hs | 26 ++++++++++++++++++++------ compiler/llvmGen/LlvmCodeGen/Base.hs | 6 +++--- compiler/main/CodeOutput.hs | 1 - 3 files changed, 23 insertions(+), 10 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen.hs b/compiler/llvmGen/LlvmCodeGen.hs index 5596d59..00f52da 100644 --- a/compiler/llvmGen/LlvmCodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen.hs @@ -40,7 +40,7 @@ import System.IO -- llvmCodeGen :: DynFlags -> Handle -> UniqSupply -> Stream.Stream IO RawCmmGroup () - -> IO () + -> IO ManglerInfo llvmCodeGen dflags h us cmm_stream = withTiming (pure dflags) (text "LLVM CodeGen") (const ()) $ do bufh <- newBufHandle h @@ -63,12 +63,13 @@ llvmCodeGen dflags h us cmm_stream $+$ text "We will try though...") -- run code generation - runLlvm dflags ver bufh us $ - llvmCodeGen' (liftStream cmm_stream) + info <- runLlvm dflags ver bufh us $ + llvmCodeGen' (liftStream cmm_stream) bFlush bufh + return info -llvmCodeGen' :: Stream.Stream LlvmM RawCmmGroup () -> LlvmM () +llvmCodeGen' :: Stream.Stream LlvmM RawCmmGroup () -> LlvmM ManglerInfo llvmCodeGen' cmm_stream = do -- Preamble renderLlvm pprLlvmHeader @@ -77,7 +78,7 @@ llvmCodeGen' cmm_stream -- Procedures let llvmStream = Stream.mapM llvmGroupLlvmGens cmm_stream - _ <- Stream.collect llvmStream + infos <- Stream.collect llvmStream -- Declare aliases for forward references renderLlvm . pprLlvmData =<< generateExternDecls @@ -85,7 +86,12 @@ llvmCodeGen' cmm_stream -- Postamble cmmUsedLlvmGens -llvmGroupLlvmGens :: RawCmmGroup -> LlvmM () + -- combine all info + let info = foldl mapUnion mapEmpty infos + + return $ Just info + +llvmGroupLlvmGens :: RawCmmGroup -> LlvmM (LabelMap CmmStatics) llvmGroupLlvmGens cmm = do -- Insert functions into map, collect data @@ -100,11 +106,19 @@ llvmGroupLlvmGens cmm = do return Nothing cdata <- fmap catMaybes $ mapM split cmm + -- collect mangler info + let joinInfo acc grp = case grp of + CmmProc info _ _ _ -> mapUnion acc info + CmmData _ _ -> acc + info = foldl joinInfo mapEmpty cmm + {-# SCC "llvm_datas_gen" #-} cmmDataLlvmGens cdata {-# SCC "llvm_procs_gen" #-} mapM_ cmmLlvmGen cmm + return info + -- ----------------------------------------------------------------------------- -- | Do LLVM code generation on all these Cmms data sections. -- diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index 47db6c4..08c2d60 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -252,10 +252,10 @@ liftIO m = LlvmM $ \env -> do x <- m return (x, env) -- | Get initial Llvm environment. -runLlvm :: DynFlags -> LlvmVersion -> BufHandle -> UniqSupply -> LlvmM () -> IO () +runLlvm :: DynFlags -> LlvmVersion -> BufHandle -> UniqSupply -> LlvmM a -> IO a runLlvm dflags ver out us m = do - _ <- runLlvmM m env - return () + (a, _) <- runLlvmM m env + return a where env = LlvmEnv { envFunMap = emptyUFM , envVarMap = emptyUFM , envStackRegs = [] diff --git a/compiler/main/CodeOutput.hs b/compiler/main/CodeOutput.hs index 5a23e06..487dd46 100644 --- a/compiler/main/CodeOutput.hs +++ b/compiler/main/CodeOutput.hs @@ -190,7 +190,6 @@ outputLlvm dflags filenm cmm_stream {-# SCC "llvm_output" #-} doOutput filenm $ \f -> {-# SCC "llvm_CodeGen" #-} llvmCodeGen dflags f ncg_uniqs cmm_stream - return Nothing -- TODO(kavon): return something {- ************************************************************************ From git at git.haskell.org Tue Jun 27 09:16:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:09 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: time to create a Rewrite for the LLVM Mangler (ce2c66f) Message-ID: <20170627091609.47D623A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/ce2c66f16e3ac46f962b736cfef21e3c319962d4/ghc >--------------------------------------------------------------- commit ce2c66f16e3ac46f962b736cfef21e3c319962d4 Author: Kavon Farvardin Date: Mon Jun 5 15:04:40 2017 +0100 time to create a Rewrite for the LLVM Mangler >--------------------------------------------------------------- ce2c66f16e3ac46f962b736cfef21e3c319962d4 compiler/llvmGen/LlvmMangler.hs | 6 ++++-- compiler/main/DriverPipeline.hs | 2 +- 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs index acf344f..0bdb688 100644 --- a/compiler/llvmGen/LlvmMangler.hs +++ b/compiler/llvmGen/LlvmMangler.hs @@ -19,10 +19,12 @@ import Outputable ( text ) import Control.Exception import qualified Data.ByteString.Char8 as B import System.IO +import Cmm +import Compiler.Hoopl -- | Read in assembly file and process -llvmFixupAsm :: DynFlags -> FilePath -> FilePath -> IO () -llvmFixupAsm dflags f1 f2 = {-# SCC "llvm_mangler" #-} +llvmFixupAsm :: DynFlags -> LabelMap CmmStatics -> FilePath -> FilePath -> IO () +llvmFixupAsm dflags gcInfo f1 f2 = {-# SCC "llvm_mangler" #-} withTiming (pure dflags) (text "LLVM Mangler") id $ withBinaryFile f1 ReadMode $ \r -> withBinaryFile f2 WriteMode $ \w -> do go r w diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 2a94105..d184418 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1551,7 +1551,7 @@ runPhase (RealPhaseWithInfo (Just info) LlvmMangle) input_fn dflags = do let next_phase = if gopt Opt_SplitObjs dflags then Splitter else As False output_fn <- phaseOutputFilename next_phase - liftIO $ llvmFixupAsm dflags input_fn output_fn + liftIO $ llvmFixupAsm dflags info input_fn output_fn return (RealPhase next_phase, output_fn) runPhase (RealPhaseWithInfo Nothing LlvmMangle) _ _ = panic "phase LlvmMangle needs info!" From git at git.haskell.org Tue Jun 27 09:16:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:11 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: setup (cf55006) Message-ID: <20170627091611.EDE9C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/cf55006b50c0282740b81876dc105527875718fd/ghc >--------------------------------------------------------------- commit cf55006b50c0282740b81876dc105527875718fd Author: Kavon Farvardin Date: Mon Jun 5 15:09:43 2017 +0100 setup >--------------------------------------------------------------- cf55006b50c0282740b81876dc105527875718fd compiler/llvmGen/LlvmMangler.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs index 0bdb688..cc8cf3b 100644 --- a/compiler/llvmGen/LlvmMangler.hs +++ b/compiler/llvmGen/LlvmMangler.hs @@ -35,17 +35,20 @@ llvmFixupAsm dflags gcInfo f1 f2 = {-# SCC "llvm_mangler" #-} go :: Handle -> Handle -> IO () go r w = do e_l <- try $ B.hGetLine r ::IO (Either IOError B.ByteString) - let writeline a = B.hPutStrLn w (rewriteLine dflags rewrites a) >> go r w + let writeline a = B.hPutStrLn w (rewriteLine dflags (rewrites gcInfo) a) >> go r w case e_l of Right l -> writeline l Left _ -> return () -- | These are the rewrites that the mangler will perform -rewrites :: [Rewrite] -rewrites = [rewriteSymType, rewriteAVX] +rewrites :: LabelMap CmmStatics -> [Rewrite] +rewrites info = [rewriteSymType, rewriteAVX, addInfoTable info] type Rewrite = DynFlags -> B.ByteString -> Maybe B.ByteString +addInfoTable :: LabelMap CmmStatics -> Rewrite +addInfoTable info dflags line = Nothing -- TODO(kavon): fill this in + -- | Rewrite a line of assembly source with the given rewrites, -- taking the first rewrite that applies. rewriteLine :: DynFlags -> [Rewrite] -> B.ByteString -> B.ByteString From git at git.haskell.org Tue Jun 27 09:16:14 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:14 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: ugh, rewrites in the mangler cannot be applied to labels right now (bd59a21) Message-ID: <20170627091614.A0D373A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/bd59a21f83c32efb3dcd3a605fffa6423330f1ea/ghc >--------------------------------------------------------------- commit bd59a21f83c32efb3dcd3a605fffa6423330f1ea Author: Kavon Farvardin Date: Tue Jun 6 15:48:54 2017 +0100 ugh, rewrites in the mangler cannot be applied to labels right now >--------------------------------------------------------------- bd59a21f83c32efb3dcd3a605fffa6423330f1ea compiler/llvmGen/LlvmMangler.hs | 55 +++++++++++++++++++++++++++++++++++++++-- compiler/main/DriverPipeline.hs | 1 + 2 files changed, 54 insertions(+), 2 deletions(-) diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs index cc8cf3b..f9b41a5 100644 --- a/compiler/llvmGen/LlvmMangler.hs +++ b/compiler/llvmGen/LlvmMangler.hs @@ -21,6 +21,8 @@ import qualified Data.ByteString.Char8 as B import System.IO import Cmm import Compiler.Hoopl +import Compiler.Hoopl.Internals ( uniqueToLbl ) +import Data.List ( intersperse ) -- | Read in assembly file and process llvmFixupAsm :: DynFlags -> LabelMap CmmStatics -> FilePath -> FilePath -> IO () @@ -42,12 +44,61 @@ llvmFixupAsm dflags gcInfo f1 f2 = {-# SCC "llvm_mangler" #-} -- | These are the rewrites that the mangler will perform rewrites :: LabelMap CmmStatics -> [Rewrite] -rewrites info = [rewriteSymType, rewriteAVX, addInfoTable info] +rewrites info = [addInfoTable info] -- TODO(kavon): reenable [rewriteSymType, rewriteAVX, addInfoTable info] type Rewrite = DynFlags -> B.ByteString -> Maybe B.ByteString +-- XXX(kavon): debug only delete me later +withComment :: String -> B.ByteString -> B.ByteString +withComment com line = B.concat [B.pack $ wrap com, line] + where + wrap c = "## comment -- " ++ c ++ "\n" + +-- | This rewrite looks for return points of a llvm.cpscall and adds GC info +-- above that label. addInfoTable :: LabelMap CmmStatics -> Rewrite -addInfoTable info dflags line = Nothing -- TODO(kavon): fill this in +addInfoTable info _ line = do + return $ withComment (show line) line + -- labName <- B.stripPrefix labPrefix line + -- return $ withComment "stripped an L" labName + -- (i, _) <- B.readInt labName + -- return $ withComment (show i) line + -- statics <- mapLookup (toKey i) info + -- return $ emitInfo line statics + + where + labPrefix = B.pack "\nL" -- TODO(kavon): check if this changes on different platforms. + toKey = uniqueToLbl . intToUnique + eol = "\n" + + emitInfo label (Statics _ statics) = + -- TODO(kavon): maybe put an alignment directive first? + B.concat $ (map staticToByteStr statics) ++ [label] + + staticToByteStr :: CmmStatic -> B.ByteString + staticToByteStr (CmmUninitialised sz) = let + width = gcd sz 8 + zeroes = take (sz `div` width) ['0','0'..] + name = szName width + in + B.pack $ name ++ (intersperse ',' zeroes) ++ eol + + staticToByteStr (CmmStaticLit (CmmLabelDiffOff _ _ _)) = B.pack "# label diff static\n" + + staticToByteStr _ = B.pack "# todo: other static\n" + + -- TODO(kavon): does this change on ARM? + -- translate a size (in bytes) to its assembly directive, followed by a space. + szName :: Int -> String + szName 1 = ".byte " + szName 2 = ".value " + szName 4 = ".long " + szName 8 = ".quad " + szName _ = error "szName -- invalid byte width" + + + + -- | Rewrite a line of assembly source with the given rewrites, -- taking the first rewrite that applies. diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index d184418..5e683eb 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -802,6 +802,7 @@ getOutputFilename stop_phase output basename dflags next_phase maybe_location keep_this_output = case next_phase of As _ | keep_s -> True + LlvmMangle | keep_s -> True LlvmOpt | keep_bc -> True HCc | keep_hc -> True _other -> False From git at git.haskell.org Tue Jun 27 09:16:17 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:17 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: adding support for rewriting labels in the LLVM Mangler (584ad81) Message-ID: <20170627091617.54E793A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/584ad81133bd684d4a0e3b0eef3ec4eb09da6611/ghc >--------------------------------------------------------------- commit 584ad81133bd684d4a0e3b0eef3ec4eb09da6611 Author: Kavon Farvardin Date: Tue Jun 6 16:48:13 2017 +0100 adding support for rewriting labels in the LLVM Mangler >--------------------------------------------------------------- 584ad81133bd684d4a0e3b0eef3ec4eb09da6611 compiler/llvmGen/LlvmMangler.hs | 38 ++++++++++++++++++++++++-------------- 1 file changed, 24 insertions(+), 14 deletions(-) diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs index f9b41a5..ed38202 100644 --- a/compiler/llvmGen/LlvmMangler.hs +++ b/compiler/llvmGen/LlvmMangler.hs @@ -23,6 +23,7 @@ import Cmm import Compiler.Hoopl import Compiler.Hoopl.Internals ( uniqueToLbl ) import Data.List ( intersperse ) +import Data.Maybe ( fromMaybe ) -- | Read in assembly file and process llvmFixupAsm :: DynFlags -> LabelMap CmmStatics -> FilePath -> FilePath -> IO () @@ -34,17 +35,23 @@ llvmFixupAsm dflags gcInfo f1 f2 = {-# SCC "llvm_mangler" #-} hClose w return () where + doRewrite a = rewriteLine dflags (labRewrites gcInfo) rewrites a + go :: Handle -> Handle -> IO () go r w = do e_l <- try $ B.hGetLine r ::IO (Either IOError B.ByteString) - let writeline a = B.hPutStrLn w (rewriteLine dflags (rewrites gcInfo) a) >> go r w + let writeline a = B.hPutStrLn w (doRewrite a) >> go r w case e_l of Right l -> writeline l Left _ -> return () --- | These are the rewrites that the mangler will perform -rewrites :: LabelMap CmmStatics -> [Rewrite] -rewrites info = [addInfoTable info] -- TODO(kavon): reenable [rewriteSymType, rewriteAVX, addInfoTable info] +-- | These are the non-label rewrites that the mangler will perform +rewrites :: [Rewrite] +rewrites = [rewriteSymType, rewriteAVX] + +-- | These are the label-based rewrites that the mangler will perform +labRewrites :: LabelMap CmmStatics -> [Rewrite] +labRewrites info = [addInfoTable info] type Rewrite = DynFlags -> B.ByteString -> Maybe B.ByteString @@ -97,21 +104,24 @@ addInfoTable info _ line = do szName _ = error "szName -- invalid byte width" - - - -- | Rewrite a line of assembly source with the given rewrites, --- taking the first rewrite that applies. -rewriteLine :: DynFlags -> [Rewrite] -> B.ByteString -> B.ByteString -rewriteLine dflags rewrites l = - case firstJust $ map (\rewrite -> rewrite dflags rest) rewrites of - Nothing -> l - Just rewritten -> B.concat $ [symbol, B.pack "\t", rewritten] +-- taking the first rewrite that applies for each kind of rewrite (label and non-label). +rewriteLine :: DynFlags -> [Rewrite] -> [Rewrite] -> B.ByteString -> B.ByteString +rewriteLine dflags labRewrites rewrites l = + case (maybNewSym, maybNewRest) of + (Nothing, Nothing) -> l -- avoid concat + (newS, newR) -> cat (fromMaybe symbol newS) (fromMaybe rest newR) where + cat sym rst = B.concat $ [sym, B.pack "\t", rst] + + findRwOf txt rws = firstJust $ map (\rw -> rw dflags txt) rws + (symbol, rest) = splitLine l + maybNewSym = findRwOf symbol labRewrites -- check for new label part + maybNewRest = findRwOf rest rewrites -- check for new non-label part firstJust :: [Maybe a] -> Maybe a - firstJust (Just x:_) = Just x + firstJust (jx@(Just _):_) = jx firstJust [] = Nothing firstJust (_:rest) = firstJust rest From git at git.haskell.org Tue Jun 27 09:16:20 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:20 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: need to do preprocessing of CmmStatics (6bb6535) Message-ID: <20170627091620.0AA523A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/6bb6535b1384c6727725ceee410fe7f2ed981f06/ghc >--------------------------------------------------------------- commit 6bb6535b1384c6727725ceee410fe7f2ed981f06 Author: Kavon Farvardin Date: Tue Jun 6 17:16:11 2017 +0100 need to do preprocessing of CmmStatics >--------------------------------------------------------------- 6bb6535b1384c6727725ceee410fe7f2ed981f06 compiler/llvmGen/LlvmMangler.hs | 64 ++++++++++++++++++++--------------------- 1 file changed, 31 insertions(+), 33 deletions(-) diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs index ed38202..4a93b37 100644 --- a/compiler/llvmGen/LlvmMangler.hs +++ b/compiler/llvmGen/LlvmMangler.hs @@ -65,43 +65,41 @@ withComment com line = B.concat [B.pack $ wrap com, line] -- above that label. addInfoTable :: LabelMap CmmStatics -> Rewrite addInfoTable info _ line = do - return $ withComment (show line) line - -- labName <- B.stripPrefix labPrefix line - -- return $ withComment "stripped an L" labName - -- (i, _) <- B.readInt labName - -- return $ withComment (show i) line - -- statics <- mapLookup (toKey i) info + labName <- B.stripPrefix labPrefix line + (i, _) <- B.readInt labName + statics <- mapLookup (toKey i) info + return $ withComment ("found statics for: " ++ show i) line -- return $ emitInfo line statics where - labPrefix = B.pack "\nL" -- TODO(kavon): check if this changes on different platforms. + labPrefix = B.pack "L" -- TODO(kavon): check if this changes on different platforms. toKey = uniqueToLbl . intToUnique - eol = "\n" - - emitInfo label (Statics _ statics) = - -- TODO(kavon): maybe put an alignment directive first? - B.concat $ (map staticToByteStr statics) ++ [label] - - staticToByteStr :: CmmStatic -> B.ByteString - staticToByteStr (CmmUninitialised sz) = let - width = gcd sz 8 - zeroes = take (sz `div` width) ['0','0'..] - name = szName width - in - B.pack $ name ++ (intersperse ',' zeroes) ++ eol - - staticToByteStr (CmmStaticLit (CmmLabelDiffOff _ _ _)) = B.pack "# label diff static\n" - - staticToByteStr _ = B.pack "# todo: other static\n" - - -- TODO(kavon): does this change on ARM? - -- translate a size (in bytes) to its assembly directive, followed by a space. - szName :: Int -> String - szName 1 = ".byte " - szName 2 = ".value " - szName 4 = ".long " - szName 8 = ".quad " - szName _ = error "szName -- invalid byte width" + -- eol = "\n" + -- + -- emitInfo label (Statics _ statics) = + -- -- TODO(kavon): maybe put an alignment directive first? + -- B.concat $ (map staticToByteStr statics) ++ [label] + -- + -- staticToByteStr :: CmmStatic -> B.ByteString + -- staticToByteStr (CmmUninitialised sz) = let + -- width = gcd sz 8 + -- zeroes = take (sz `div` width) ['0','0'..] + -- name = szName width + -- in + -- B.pack $ name ++ (intersperse ',' zeroes) ++ eol + -- + -- staticToByteStr (CmmStaticLit (CmmLabelDiffOff _ _ _)) = B.pack "# label diff static\n" + -- + -- staticToByteStr _ = B.pack "# todo: other static\n" + -- + -- -- TODO(kavon): does this change on ARM? + -- -- translate a size (in bytes) to its assembly directive, followed by a space. + -- szName :: Int -> String + -- szName 1 = ".byte " + -- szName 2 = ".value " + -- szName 4 = ".long " + -- szName 8 = ".quad " + -- szName _ = error "szName -- invalid byte width" -- | Rewrite a line of assembly source with the given rewrites, From git at git.haskell.org Tue Jun 27 09:16:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:22 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: we need a mapMapM... can we lift it or something? (5b74c98) Message-ID: <20170627091622.BA9B63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/5b74c98369acbf9c6e7598ae642a9250fde0116a/ghc >--------------------------------------------------------------- commit 5b74c98369acbf9c6e7598ae642a9250fde0116a Author: Kavon Farvardin Date: Tue Jun 6 18:47:55 2017 +0100 we need a mapMapM... can we lift it or something? >--------------------------------------------------------------- 5b74c98369acbf9c6e7598ae642a9250fde0116a compiler/cmm/Cmm.hs | 3 +-- compiler/ghc.mk | 46 +++++++++++------------------------- compiler/llvmGen/LlvmCodeGen.hs | 21 +++++++++------- compiler/llvmGen/LlvmCodeGen/Data.hs | 8 ++++++- compiler/llvmGen/LlvmMangler.hs | 13 +++++----- compiler/main/PipelineMonad.hs | 2 +- 6 files changed, 42 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 5b74c98369acbf9c6e7598ae642a9250fde0116a From git at git.haskell.org Tue Jun 27 09:16:25 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:25 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: just using mapToList; the maps aren't big anyways (6c1e020) Message-ID: <20170627091625.6EC8A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/6c1e0203383a451ad1d246c9a8c606ff5ed208d3/ghc >--------------------------------------------------------------- commit 6c1e0203383a451ad1d246c9a8c606ff5ed208d3 Author: Kavon Farvardin Date: Wed Jun 7 11:27:15 2017 +0100 just using mapToList; the maps aren't big anyways >--------------------------------------------------------------- 6c1e0203383a451ad1d246c9a8c606ff5ed208d3 compiler/llvmGen/LlvmCodeGen.hs | 7 ++++++- compiler/llvmGen/LlvmCodeGen/Data.hs | 3 ++- compiler/main/CodeOutput.hs | 3 ++- compiler/main/HscMain.hs | 1 + 4 files changed, 11 insertions(+), 3 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen.hs b/compiler/llvmGen/LlvmCodeGen.hs index b3a8cec..35c24aa 100644 --- a/compiler/llvmGen/LlvmCodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen.hs @@ -116,10 +116,15 @@ llvmGroupLlvmGens cmm = do joinInfo :: LabelMap ManglerStr -> RawCmmDecl -> LlvmM (LabelMap ManglerStr) joinInfo acc grp = case grp of CmmProc info _ _ _ -> do - newInfo <- mapMap cvtForMangler info + let asL = mapToList info + newInfo <- foldM cvt mapEmpty asL return $ mapUnion acc newInfo CmmData _ _ -> return acc + cvt acc (key, val) = do + str <- cvtForMangler val + return $ mapInsert key str acc + foldM joinInfo mapEmpty cmm -- ----------------------------------------------------------------------------- diff --git a/compiler/llvmGen/LlvmCodeGen/Data.hs b/compiler/llvmGen/LlvmCodeGen/Data.hs index 4a97ff6..7be62d9 100644 --- a/compiler/llvmGen/LlvmCodeGen/Data.hs +++ b/compiler/llvmGen/LlvmCodeGen/Data.hs @@ -11,6 +11,7 @@ module LlvmCodeGen.Data ( import Llvm import LlvmCodeGen.Base +import LlvmMangler ( ManglerStr ) import BlockId import CLabel @@ -152,5 +153,5 @@ genStaticLit (CmmHighStackMark) -- | Convert a CmmStatic into a byte string for the mangler -cvtForMangler :: CmmStatics -> LlvmM B.ByteString +cvtForMangler :: CmmStatics -> LlvmM ManglerStr cvtForMangler _ = error "implement cvtForMangler" diff --git a/compiler/main/CodeOutput.hs b/compiler/main/CodeOutput.hs index 487dd46..2f50105 100644 --- a/compiler/main/CodeOutput.hs +++ b/compiler/main/CodeOutput.hs @@ -19,13 +19,14 @@ import Finder ( mkStubPaths ) import PprC ( writeCs ) import CmmLint ( cmmLint ) import Packages -import Cmm ( RawCmmGroup, ManglerInfo ) +import Cmm ( RawCmmGroup ) import HscTypes import DynFlags import Config import SysTools import Stream (Stream) import qualified Stream +import LlvmMangler ( ManglerInfo ) import ErrUtils import Outputable diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index 7c660b0..10175c6 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -137,6 +137,7 @@ import FamInstEnv import Fingerprint ( Fingerprint ) import Hooks import TcEnv +import LlvmMangler ( ManglerInfo ) import DynFlags import ErrUtils From git at git.haskell.org Tue Jun 27 09:16:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:28 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: finally got the types the way I want them (9172e98) Message-ID: <20170627091628.223383A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/9172e98d75685cc7859ced813b04523df1f8b057/ghc >--------------------------------------------------------------- commit 9172e98d75685cc7859ced813b04523df1f8b057 Author: Kavon Farvardin Date: Wed Jun 7 15:11:03 2017 +0100 finally got the types the way I want them >--------------------------------------------------------------- 9172e98d75685cc7859ced813b04523df1f8b057 compiler/llvmGen/LlvmCodeGen/Data.hs | 16 ++++++++++++++-- compiler/llvmGen/LlvmMangler.hs | 14 +++++++++++++- 2 files changed, 27 insertions(+), 3 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Data.hs b/compiler/llvmGen/LlvmCodeGen/Data.hs index 7be62d9..436438d 100644 --- a/compiler/llvmGen/LlvmCodeGen/Data.hs +++ b/compiler/llvmGen/LlvmCodeGen/Data.hs @@ -152,6 +152,18 @@ genStaticLit (CmmHighStackMark) = panic "genStaticLit: CmmHighStackMark unsupported!" --- | Convert a CmmStatic into a byte string for the mangler +-- | Convert a CmmStatic into a byte string for the LLVM mangler. +-- The mangler will insert the ManglerStr representations of the +-- CmmStatic at return points of a cpscall. cvtForMangler :: CmmStatics -> LlvmM ManglerStr -cvtForMangler _ = error "implement cvtForMangler" +cvtForMangler (Statics _ datum) = + mapM doStatic datum + where + doStatic :: CmmStatic -> LlvmM (B.ByteString -> B.ByteString) + doStatic (CmmStaticLit lit) = return $ \ _ -> B.pack "## todo" + + -- XXX these are not expected to appear at return points at the moment. + doStatic (CmmUninitialised _) = error "doStatic -- uninit unhandled" + doStatic (CmmString _) = error "doStatic -- string unhandled" + + diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs index fc3b11e..63d7d41 100644 --- a/compiler/llvmGen/LlvmMangler.hs +++ b/compiler/llvmGen/LlvmMangler.hs @@ -23,7 +23,19 @@ import Compiler.Hoopl import Compiler.Hoopl.Internals ( uniqueToLbl ) import Data.Maybe ( fromMaybe ) -type ManglerStr = B.ByteString +-- note [mangler string func] +-- A ManglerStr takes the name of the label it will be attached to, +-- and returns the data that should appear before that label. +-- We do this because some of the static data is of the form +-- +-- .quad SRT_LAB-CUR_LABEL +-- +-- and we do not have a name for CUR_LABEL until LLVM generates +-- the assembly code for the function. The name for SRT_LAB +-- is only in the LLVM monad, so we need two stages to generate +-- that line + +type ManglerStr = [B.ByteString -> B.ByteString] type ManglerInfo = Maybe (LabelMap ManglerStr) -- | Read in assembly file and process From git at git.haskell.org Tue Jun 27 09:16:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:30 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: cleaning up cruft (0f36feb) Message-ID: <20170627091630.CF98C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/0f36feb9f94bab99b0e1e64fd996fb9911182c70/ghc >--------------------------------------------------------------- commit 0f36feb9f94bab99b0e1e64fd996fb9911182c70 Author: Kavon Farvardin Date: Wed Jun 7 15:38:53 2017 +0100 cleaning up cruft >--------------------------------------------------------------- 0f36feb9f94bab99b0e1e64fd996fb9911182c70 compiler/llvmGen/LlvmCodeGen/Data.hs | 48 ++++++++++++++++++++++++++++++++---- compiler/llvmGen/LlvmMangler.hs | 40 ++++++------------------------ 2 files changed, 50 insertions(+), 38 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Data.hs b/compiler/llvmGen/LlvmCodeGen/Data.hs index 436438d..4996aeb 100644 --- a/compiler/llvmGen/LlvmCodeGen/Data.hs +++ b/compiler/llvmGen/LlvmCodeGen/Data.hs @@ -157,13 +157,51 @@ genStaticLit (CmmHighStackMark) -- CmmStatic at return points of a cpscall. cvtForMangler :: CmmStatics -> LlvmM ManglerStr cvtForMangler (Statics _ datum) = - mapM doStatic datum + mapM cvtStatic datum where - doStatic :: CmmStatic -> LlvmM (B.ByteString -> B.ByteString) - doStatic (CmmStaticLit lit) = return $ \ _ -> B.pack "## todo" + cvtStatic :: CmmStatic -> LlvmM (B.ByteString -> B.ByteString) + cvtStatic (CmmStaticLit lit) = cvtLit lit -- XXX these are not expected to appear at return points at the moment. - doStatic (CmmUninitialised _) = error "doStatic -- uninit unhandled" - doStatic (CmmString _) = error "doStatic -- string unhandled" + cvtStatic (CmmUninitialised _) = error "cvtStatic -- uninit unhandled" + cvtStatic (CmmString _) = error "cvtStatic -- string unhandled" + + + cvtLit _ = return $ test $ B.pack "## todo: some other CmmLit for " + + some bstr _ = bstr + + test bstr lab = B.concat [ + bstr, + lab, + B.pack "\n" + ] + + -- eol = "\n" + -- + -- emitInfo label (Statics _ statics) = + -- -- TODO(kavon): maybe put an alignment directive first? + -- B.concat $ (map staticToByteStr statics) ++ [label] + -- + -- staticToByteStr :: CmmStatic -> B.ByteString + -- staticToByteStr (CmmUninitialised sz) = let + -- width = gcd sz 8 + -- zeroes = take (sz `div` width) ['0','0'..] + -- name = szName width + -- in + -- B.pack $ name ++ (intersperse ',' zeroes) ++ eol + -- + -- staticToByteStr (CmmStaticLit (CmmLabelDiffOff _ _ _)) = B.pack "# label diff static\n" + -- + -- staticToByteStr _ = B.pack "# todo: other static\n" + -- + -- -- TODO(kavon): does this change on ARM? + -- -- translate a size (in bytes) to its assembly directive, followed by a space. + -- szName :: Int -> String + -- szName 1 = ".byte " + -- szName 2 = ".value " + -- szName 4 = ".long " + -- szName 8 = ".quad " + -- szName _ = error "szName -- invalid byte width" diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs index 63d7d41..27f4a1f 100644 --- a/compiler/llvmGen/LlvmMangler.hs +++ b/compiler/llvmGen/LlvmMangler.hs @@ -78,42 +78,16 @@ withComment com line = B.concat [B.pack $ wrap com, line] -- above that label. addInfoTable :: LabelMap ManglerStr -> Rewrite addInfoTable info _ line = do - labName <- B.stripPrefix labPrefix line - (i, _) <- B.readInt labName + retPt <- B.stripPrefix labPrefix line + (i, _) <- B.readInt retPt statics <- mapLookup (toKey i) info - return $ withComment ("found statics for: " ++ show i) line - -- return $ emitInfo line statics - + fullName <- B.stripSuffix colon line + return $ B.concat $ (map (\f -> f fullName) statics) ++ [line] where - labPrefix = B.pack "L" -- TODO(kavon): check if this changes on different platforms. + -- TODO(kavon): check if prefix changes on different platforms. + labPrefix = B.pack "L" + colon = B.pack ":" toKey = uniqueToLbl . intToUnique - -- eol = "\n" - -- - -- emitInfo label (Statics _ statics) = - -- -- TODO(kavon): maybe put an alignment directive first? - -- B.concat $ (map staticToByteStr statics) ++ [label] - -- - -- staticToByteStr :: CmmStatic -> B.ByteString - -- staticToByteStr (CmmUninitialised sz) = let - -- width = gcd sz 8 - -- zeroes = take (sz `div` width) ['0','0'..] - -- name = szName width - -- in - -- B.pack $ name ++ (intersperse ',' zeroes) ++ eol - -- - -- staticToByteStr (CmmStaticLit (CmmLabelDiffOff _ _ _)) = B.pack "# label diff static\n" - -- - -- staticToByteStr _ = B.pack "# todo: other static\n" - -- - -- -- TODO(kavon): does this change on ARM? - -- -- translate a size (in bytes) to its assembly directive, followed by a space. - -- szName :: Int -> String - -- szName 1 = ".byte " - -- szName 2 = ".value " - -- szName 4 = ".long " - -- szName 8 = ".quad " - -- szName _ = error "szName -- invalid byte width" - -- | Rewrite a line of assembly source with the given rewrites, -- taking the first rewrite that applies for each kind of rewrite (label and non-label). From git at git.haskell.org Tue Jun 27 09:16:33 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:33 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: working on CmmLabelDiffOff (09fb036) Message-ID: <20170627091633.8494E3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/09fb036c6399a410578b27bc704215c22f281b54/ghc >--------------------------------------------------------------- commit 09fb036c6399a410578b27bc704215c22f281b54 Author: Kavon Farvardin Date: Wed Jun 7 16:11:58 2017 +0100 working on CmmLabelDiffOff >--------------------------------------------------------------- 09fb036c6399a410578b27bc704215c22f281b54 compiler/llvmGen/LlvmCodeGen/Data.hs | 46 +++++++++++++++++++++++------------- 1 file changed, 30 insertions(+), 16 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Data.hs b/compiler/llvmGen/LlvmCodeGen/Data.hs index 4996aeb..8e03d74 100644 --- a/compiler/llvmGen/LlvmCodeGen/Data.hs +++ b/compiler/llvmGen/LlvmCodeGen/Data.hs @@ -161,21 +161,40 @@ cvtForMangler (Statics _ datum) = where cvtStatic :: CmmStatic -> LlvmM (B.ByteString -> B.ByteString) cvtStatic (CmmStaticLit lit) = cvtLit lit + cvtStatic _ = error "cvtStatic -- unexpected static kind" - -- XXX these are not expected to appear at return points at the moment. - cvtStatic (CmmUninitialised _) = error "cvtStatic -- uninit unhandled" - cvtStatic (CmmString _) = error "cvtStatic -- string unhandled" + cvtLit (CmmInt i w) = return $ just $ B.concat [ + szName w, + B.pack $ show i, + eol + ] + -- NB: we do not check label2 of this lit because of the + -- limitations described in CmmExpr.hs. What that boils down + -- to is, for an info table of this form: + -- + -- Statics a [..., (CmmLabelDiff _ b _), ...] + -- + -- then a == b. We rely on this property when creating + -- its corresponding byte string. + cvtLit (CmmLabelDiffOff srt _ off) = do + var <- getGlobalPtr =<< strCLabel_llvm srt + return $ dbg (B.pack "## diffOff -- get name of var ") - cvtLit _ = return $ test $ B.pack "## todo: some other CmmLit for " + cvtLit _ = return $ dbg (B.pack "## some other lit for ") - some bstr _ = bstr - test bstr lab = B.concat [ - bstr, - lab, - B.pack "\n" - ] + just bstr _ = bstr + dbg bstr lab = B.concat [bstr, lab, eol] + + szName :: Width -> B.ByteString + szName W8 = B.pack "\t.byte\t" + szName W16 = B.pack "\t.value\t" + szName W32 = B.pack "\t.long\t" + szName W64 = B.pack "\t.quad\t" + szName _ = error "szName -- invalid CmmInt width" + + eol = B.pack "\n" -- eol = "\n" -- @@ -197,11 +216,6 @@ cvtForMangler (Statics _ datum) = -- -- -- TODO(kavon): does this change on ARM? -- -- translate a size (in bytes) to its assembly directive, followed by a space. - -- szName :: Int -> String - -- szName 1 = ".byte " - -- szName 2 = ".value " - -- szName 4 = ".long " - -- szName 8 = ".quad " - -- szName _ = error "szName -- invalid byte width" + -- From git at git.haskell.org Tue Jun 27 09:16:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:38 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: nofib's queens works fine now! (14d0045) Message-ID: <20170627091638.E54BA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/14d00455f98f269374f57f6047005972af1c42fe/ghc >--------------------------------------------------------------- commit 14d00455f98f269374f57f6047005972af1c42fe Author: Kavon Farvardin Date: Wed Jun 7 17:24:34 2017 +0100 nofib's queens works fine now! >--------------------------------------------------------------- 14d00455f98f269374f57f6047005972af1c42fe compiler/llvmGen/LlvmCodeGen/Base.hs | 8 ++++++-- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 2 +- compiler/llvmGen/LlvmCodeGen/Ppr.hs | 2 +- 3 files changed, 8 insertions(+), 4 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index 08c2d60..d34aaed 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -26,7 +26,7 @@ module LlvmCodeGen.Base ( cmmToLlvmType, widthToLlvmFloat, widthToLlvmInt, llvmFunTy, llvmFunSig, llvmFunArgs, llvmStdFunAttrs, llvmFunAlign, llvmInfAlign, - llvmPtrBits, tysToParams, llvmFunSection, llvmStdConv, + llvmPtrBits, tysToParams, llvmFunSection, llvmStdConv, llvmStdFunDefAttrs, strCLabel_llvm, strDisplayName_llvm, strProcedureName_llvm, getGlobalPtr, generateExternDecls, @@ -166,10 +166,14 @@ llvmFunArgs dflags live = map (lmGlobalRegArg dflags) (llvmStdConv dflags live) --- | Llvm standard fun attributes +-- | Llvm standard function call attributes llvmStdFunAttrs :: [LlvmFuncAttr] llvmStdFunAttrs = [NoUnwind] +-- | Llvm standard function definition attributes +llvmStdFunDefAttrs :: [LlvmFuncAttr] +llvmStdFunDefAttrs = [NoUnwind, Naked] + -- | Convert a list of types to a list of function parameters -- (each with no parameter attributes) tysToParams :: [LlvmType] -> [LlvmParameter] diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 4b8d4ae..eee57a3 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -445,7 +445,7 @@ genCall target res args = runStmtsDecls $ do fptr <- getFunPtrW funTy target let doReturn | ccTy == TailCall = statement $ Return Nothing - | never_returns = statement $ Unreachable + | never_returns = statement $ Unreachable -- TODO(kavon): this breaks TCO | otherwise = return () doTrashStmts diff --git a/compiler/llvmGen/LlvmCodeGen/Ppr.hs b/compiler/llvmGen/LlvmCodeGen/Ppr.hs index 8b6340d..52c7c4f 100644 --- a/compiler/llvmGen/LlvmCodeGen/Ppr.hs +++ b/compiler/llvmGen/LlvmCodeGen/Ppr.hs @@ -129,7 +129,7 @@ pprLlvmCmmDecl (CmmProc mb_info entry_lbl live (ListGraph blks)) return $ Just $ LMStaticStruc infoStatics infoTy - let fun = LlvmFunction funDec funArgs llvmStdFunAttrs funSect + let fun = LlvmFunction funDec funArgs llvmStdFunDefAttrs funSect prefix lmblocks name = decName $ funcDecl fun defName = name `appendFS` fsLit "$def" From git at git.haskell.org Tue Jun 27 09:16:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:36 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: need to clean up but info tables are being emitted now (fc6f1f2) Message-ID: <20170627091636.38AA83A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/fc6f1f2360cfda978a0e74f34c6544a62a69f306/ghc >--------------------------------------------------------------- commit fc6f1f2360cfda978a0e74f34c6544a62a69f306 Author: Kavon Farvardin Date: Wed Jun 7 17:14:41 2017 +0100 need to clean up but info tables are being emitted now >--------------------------------------------------------------- fc6f1f2360cfda978a0e74f34c6544a62a69f306 compiler/llvmGen/LlvmCodeGen/Data.hs | 25 ++++++++++++++++++++++--- 1 file changed, 22 insertions(+), 3 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Data.hs b/compiler/llvmGen/LlvmCodeGen/Data.hs index 8e03d74..7bf4d45 100644 --- a/compiler/llvmGen/LlvmCodeGen/Data.hs +++ b/compiler/llvmGen/LlvmCodeGen/Data.hs @@ -178,13 +178,31 @@ cvtForMangler (Statics _ datum) = -- then a == b. We rely on this property when creating -- its corresponding byte string. cvtLit (CmmLabelDiffOff srt _ off) = do - var <- getGlobalPtr =<< strCLabel_llvm srt - return $ dbg (B.pack "## diffOff -- get name of var ") + srtVar <- getGlobalPtr =<< strCLabel_llvm srt + let srtLab = asmNameOf srtVar + return $ mkDiffOff srtLab off cvtLit _ = return $ dbg (B.pack "## some other lit for ") + mkDiffOff srt off mine = B.concat [ + szName W64, + srt, + B.pack "-", + mine, + B.pack ("+" ++ show off), + eol + ] - just bstr _ = bstr + -- TODO(kavon): consult dflags to put the right number of underscores on the name + asmNameOf (LMGlobalVar fs _ _ _ _ _) = let + llName = "_" ++ unpackFS fs + in + B.pack llName + + + + + -- XXX delete me later dbg bstr lab = B.concat [bstr, lab, eol] szName :: Width -> B.ByteString @@ -195,6 +213,7 @@ cvtForMangler (Statics _ datum) = szName _ = error "szName -- invalid CmmInt width" eol = B.pack "\n" + just bstr _ = bstr -- eol = "\n" -- From git at git.haskell.org Tue Jun 27 09:16:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:41 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: adding alignment to info tables (323a27f) Message-ID: <20170627091641.99D1F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/323a27f594a6d2bcd254487a84e29483d89fde83/ghc >--------------------------------------------------------------- commit 323a27f594a6d2bcd254487a84e29483d89fde83 Author: Kavon Farvardin Date: Wed Jun 7 17:44:34 2017 +0100 adding alignment to info tables >--------------------------------------------------------------- 323a27f594a6d2bcd254487a84e29483d89fde83 compiler/llvmGen/LlvmCodeGen/Data.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Data.hs b/compiler/llvmGen/LlvmCodeGen/Data.hs index 7bf4d45..c3dfc49 100644 --- a/compiler/llvmGen/LlvmCodeGen/Data.hs +++ b/compiler/llvmGen/LlvmCodeGen/Data.hs @@ -156,8 +156,10 @@ genStaticLit (CmmHighStackMark) -- The mangler will insert the ManglerStr representations of the -- CmmStatic at return points of a cpscall. cvtForMangler :: CmmStatics -> LlvmM ManglerStr -cvtForMangler (Statics _ datum) = - mapM cvtStatic datum +cvtForMangler (Statics _ datum) = do + let header = just align + body <- mapM cvtStatic datum + return $ header : body where cvtStatic :: CmmStatic -> LlvmM (B.ByteString -> B.ByteString) cvtStatic (CmmStaticLit lit) = cvtLit lit @@ -213,6 +215,7 @@ cvtForMangler (Statics _ datum) = szName _ = error "szName -- invalid CmmInt width" eol = B.pack "\n" + align = B.pack "\t.p2align\t4, 0x90\n" just bstr _ = bstr -- eol = "\n" From git at git.haskell.org Tue Jun 27 09:16:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:44 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: partial fix for type error with SSE reg values (5994a51) Message-ID: <20170627091644.670C23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/5994a511c8ae406c09c2d7c95b75344de4b5292c/ghc >--------------------------------------------------------------- commit 5994a511c8ae406c09c2d7c95b75344de4b5292c Author: Kavon Farvardin Date: Fri Jun 9 17:35:52 2017 +0100 partial fix for type error with SSE reg values >--------------------------------------------------------------- 5994a511c8ae406c09c2d7c95b75344de4b5292c compiler/llvmGen/LlvmCodeGen/Base.hs | 42 +++++++++++++++++++++++---------- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 5 ++-- 2 files changed, 33 insertions(+), 14 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index d34aaed..14e9ca2 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -27,6 +27,7 @@ module LlvmCodeGen.Base ( cmmToLlvmType, widthToLlvmFloat, widthToLlvmInt, llvmFunTy, llvmFunSig, llvmFunArgs, llvmStdFunAttrs, llvmFunAlign, llvmInfAlign, llvmPtrBits, tysToParams, llvmFunSection, llvmStdConv, llvmStdFunDefAttrs, + llvmStdRetConv, strCLabel_llvm, strDisplayName_llvm, strProcedureName_llvm, getGlobalPtr, generateExternDecls, @@ -125,10 +126,13 @@ llvmFunSig' live lbl link | otherwise = (x, []) dflags <- getDynFlags -- the standard set of argument types passed/returned. - let stdConvention = map getVarType (llvmFunArgs dflags live) - let retTy = LMStructU $ stdConvention -- TODO(kavon): introduce a type alias to reduce bytes output + let regToTy = getVarType . (lmGlobalRegArg dflags) + callConv = map getVarType (llvmFunArgs dflags live) + retConv = map regToTy (llvmStdRetConv dflags) + -- TODO(kavon): introduce a type alias for the ret struct to reduce bytes output + retTy = LMStructU $ retConv return $ LlvmFunctionDecl lbl link (llvmGhcCC dflags) retTy FixedArgs - (map toParams stdConvention) + (map toParams callConv) (llvmFunAlign dflags) -- | Alignment to use for functions @@ -146,19 +150,33 @@ llvmFunSection dflags lbl | otherwise = Nothing -- | The full set of Cmm registers passed to a function, in the correct order, --- given the live argument registers. This is used for both call and return. +-- given the live argument registers. llvmStdConv :: DynFlags -> LiveGlobalRegs -> [GlobalReg] llvmStdConv dflags live = filter isPassed (activeStgRegs platform) where platform = targetPlatform dflags - isLive r = not (isSSE r) || r `elem` alwaysLive || r `elem` live - isPassed r = not (isSSE r) || isLive r - isSSE (FloatReg _) = True - isSSE (DoubleReg _) = True - isSSE (XmmReg _) = True - isSSE (YmmReg _) = True - isSSE (ZmmReg _) = True - isSSE _ = False + isLive r = r `elem` alwaysLive || r `elem` live + isPassed r = not (isFloatReg r || isVectorReg r) || isLive r + +-- | The full set of Cmm registers returned from a function, in the correct order. +llvmStdRetConv :: DynFlags -> [GlobalReg] +llvmStdRetConv dflags = + -- NB: the return type of all LLVM fuctions must match up for tail-call optimization, + -- so we pick a safe superset of all return types here. + filter isPassed (activeStgRegs platform) + where platform = targetPlatform dflags + isPassed r = not $ isVectorReg r -- TODO(kavon): I see no reason why we can't return a vector reg + +isFloatReg :: GlobalReg -> Bool +isFloatReg (FloatReg _) = True +isFloatReg (DoubleReg _) = True +isFloatReg _ = False + +isVectorReg :: GlobalReg -> Bool +isVectorReg (XmmReg _) = True +isVectorReg (YmmReg _) = True +isVectorReg (ZmmReg _) = True +isVectorReg _ = False -- | A Function's arguments llvmFunArgs :: DynFlags -> LiveGlobalRegs -> [LlvmVar] diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index eee57a3..ab09516 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -865,8 +865,9 @@ doReturnTo (retl, _, retArgs) llRetV = do -- we could avoid emitting those extracts by slimming down the retRegs list. -- retRegs is a subset of allRegs, with the _same relative ordering_ - retRegs = llvmStdConv dflags retArgs - allRegs = activeStgRegs $ targetPlatform dflags + allRegs = llvmStdRetConv dflags + isPassed r = r `elem` retArgs || r `elem` alwaysLive + retRegs = filter isPassed allRegs extract (z@(_, [], _)) _ = return z -- no more slots needed extract (i, x:xs, stms) reg From git at git.haskell.org Tue Jun 27 09:16:47 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:47 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: turns out that we need type mangling for cpscall (2b37541) Message-ID: <20170627091647.1BFD63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/2b375416caa4bd7249ebb25e375afb8803206b89/ghc >--------------------------------------------------------------- commit 2b375416caa4bd7249ebb25e375afb8803206b89 Author: Kavon Farvardin Date: Fri Jun 9 18:13:56 2017 +0100 turns out that we need type mangling for cpscall >--------------------------------------------------------------- 2b375416caa4bd7249ebb25e375afb8803206b89 compiler/llvmGen/LlvmCodeGen/Base.hs | 34 ++++++++++++++++++++++++++++++++-- 1 file changed, 32 insertions(+), 2 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index 14e9ca2..01e0191 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -526,8 +526,7 @@ aliasify (LMGlobal var val) = do cpsCallOf :: LlvmType -> LlvmType cpsCallOf givenFn = LMFunction $ LlvmFunctionDecl { - -- NB skipping type mangling because of current assumptions - decName = fsLit "llvm.experimental.cpscall.x", + decName = fsLit $ "llvm.experimental.cpscall." ++ mangle givenFn, funcLinkage = ExternallyVisible, funcCc = CC_Ghc, decReturnType = getRetTy givenFn, @@ -537,6 +536,37 @@ cpsCallOf givenFn = LMFunction $ } where noAttr ty = (ty, []) + mangleP (ty, _) = mangle ty + + -- We need a unique name for this instance of the intrinsic, + -- which depends on to the type of the function called. + -- The nice thing is that we don't have to match LLVM's type + -- mangler function, it just has to be a valid identifier. + -- We could compute a unique hash number for the type if + -- we want to save on the length of this name. -- kavon, Jun '17 + mangle :: LlvmType -> String + mangle (LMInt sz) = 'i' : show sz + mangle LMFloat = "f32" + mangle LMDouble = "f64" + mangle (LMPointer ty) = "p0" ++ mangle ty + mangle (LMArray nr ty) = 'a' : show nr ++ mangle ty + mangle (LMVector nr ty) = 'v' : show nr ++ mangle ty + mangle (LMStruct tys) = "ps" ++ concatMap mangle tys + mangle (LMStructU tys) = 's' : concatMap mangle tys + mangle (LMFunction (LlvmFunctionDecl _ _ _ r varg p _)) + = prefix + ++ mangle r ++ "_" + ++ concatMap mangleP p ++ "_f" + where + prefix = case varg of + FixedArgs -> "f_" + VarArgs -> "fv_" + mangle LMFloat80 = "f80" + mangle LMFloat128 = "f128" + mangle LMVoid = "void" + mangle _ = error "cpsCallOf's type mangler did not expect this type!" + + -- Note [Llvm Forward References] -- From git at git.haskell.org Tue Jun 27 09:16:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:49 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: small improvements to mangler output (b61c45d) Message-ID: <20170627091649.C99B93A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/b61c45df32a765b467a2233d7b5a92f874937108/ghc >--------------------------------------------------------------- commit b61c45df32a765b467a2233d7b5a92f874937108 Author: Kavon Farvardin Date: Wed Jun 14 16:56:00 2017 +0100 small improvements to mangler output >--------------------------------------------------------------- b61c45df32a765b467a2233d7b5a92f874937108 compiler/llvmGen/LlvmCodeGen/Data.hs | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/compiler/llvmGen/LlvmCodeGen/Data.hs b/compiler/llvmGen/LlvmCodeGen/Data.hs index c3dfc49..fa31863 100644 --- a/compiler/llvmGen/LlvmCodeGen/Data.hs +++ b/compiler/llvmGen/LlvmCodeGen/Data.hs @@ -186,11 +186,21 @@ cvtForMangler (Statics _ datum) = do cvtLit _ = return $ dbg (B.pack "## some other lit for ") + mkDiffOff srt 0 mine = B.concat [ + szName W64, + srt, + B.pack "-", + mine, + eol + ] + mkDiffOff srt off mine = B.concat [ szName W64, + B.pack "(", srt, B.pack "-", mine, + B.pack ")", B.pack ("+" ++ show off), eol ] @@ -201,6 +211,8 @@ cvtForMangler (Statics _ datum) = do in B.pack llName + asmNameOf _ = error "asmNameOf -- unexpected name kind" + From git at git.haskell.org Tue Jun 27 09:16:52 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:52 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: gross workaround but I want to see if this is the only bug (05ca291) Message-ID: <20170627091652.7FF1F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/05ca2915bcf7cd072b62d6d3391b9ce9da89ba59/ghc >--------------------------------------------------------------- commit 05ca2915bcf7cd072b62d6d3391b9ce9da89ba59 Author: Kavon Farvardin Date: Wed Jun 14 17:07:35 2017 +0100 gross workaround but I want to see if this is the only bug >--------------------------------------------------------------- 05ca2915bcf7cd072b62d6d3391b9ce9da89ba59 compiler/main/DriverPipeline.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 5e683eb..3935aad 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1479,6 +1479,7 @@ runPhase (RealPhaseWithInfo mangInfo LlvmLlc) input_fn dflags liftIO $ SysTools.runLlvmLlc dflags ([ SysTools.Option (llvmOpts !! opt_lvl), + SysTools.Option cpscall_workaround, SysTools.Option $ "-relocation-model=" ++ rmodel, SysTools.FileOption "" input_fn, SysTools.Option "-o", SysTools.FileOption "" output_fn] @@ -1500,6 +1501,10 @@ runPhase (RealPhaseWithInfo mangInfo LlvmLlc) input_fn dflags return (doNext, output_fn) where + + -- TODO(kavon): temporary + cpscall_workaround = "-disable-machine-cse" + -- Bug in LLVM at O3 on OSX. llvmOpts = if platformOS (targetPlatform dflags) == OSDarwin then ["-O1", "-O2", "-O2"] From git at git.haskell.org Tue Jun 27 09:16:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:55 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: corresponding updates to mangler for stack-align issue (0a00225) Message-ID: <20170627091655.337AF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/0a0022517a189810d5904873151ffbc1964cc268/ghc >--------------------------------------------------------------- commit 0a0022517a189810d5904873151ffbc1964cc268 Author: Kavon Farvardin Date: Sat Jun 17 19:08:46 2017 +0100 corresponding updates to mangler for stack-align issue >--------------------------------------------------------------- 0a0022517a189810d5904873151ffbc1964cc268 compiler/llvmGen/LlvmCodeGen/Base.hs | 2 +- compiler/llvmGen/LlvmMangler.hs | 50 ++++++++++++++++++++++-------------- 2 files changed, 32 insertions(+), 20 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index 01e0191..943d08d 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -190,7 +190,7 @@ llvmStdFunAttrs = [NoUnwind] -- | Llvm standard function definition attributes llvmStdFunDefAttrs :: [LlvmFuncAttr] -llvmStdFunDefAttrs = [NoUnwind, Naked] +llvmStdFunDefAttrs = [NoUnwind] -- | Convert a list of types to a list of function parameters -- (each with no parameter attributes) diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs index 27f4a1f..ee7b110 100644 --- a/compiler/llvmGen/LlvmMangler.hs +++ b/compiler/llvmGen/LlvmMangler.hs @@ -43,19 +43,20 @@ llvmFixupAsm :: DynFlags -> LabelMap ManglerStr -> FilePath -> FilePath -> IO () llvmFixupAsm dflags gcInfo f1 f2 = {-# SCC "llvm_mangler" #-} withTiming (pure dflags) (text "LLVM Mangler") id $ withBinaryFile f1 ReadMode $ \r -> withBinaryFile f2 WriteMode $ \w -> do - go r w + go r w [] hClose r hClose w return () where - doRewrite a = rewriteLine dflags (labRewrites gcInfo) rewrites a + doRewrite x = rewriteLine dflags (labRewrites gcInfo) rewrites x - go :: Handle -> Handle -> IO () - go r w = do + go :: Handle -> Handle -> [Line] -> IO () + go r w pL = do e_l <- try $ B.hGetLine r ::IO (Either IOError B.ByteString) - let writeline a = B.hPutStrLn w (doRewrite a) >> go r w + let writeline x = B.hPutStrLn w newL >> go r w newPL + where (newPL, newL) = doRewrite x case e_l of - Right l -> writeline l + Right l -> writeline (pL, l) Left _ -> return () -- | These are the non-label rewrites that the mangler will perform @@ -63,10 +64,12 @@ rewrites :: [Rewrite] rewrites = [rewriteSymType, rewriteAVX] -- | These are the label-based rewrites that the mangler will perform -labRewrites :: LabelMap ManglerStr -> [Rewrite] +labRewrites :: LabelMap ManglerStr -> [LabRewrite] labRewrites info = [addInfoTable info] -type Rewrite = DynFlags -> B.ByteString -> Maybe B.ByteString +type Line = B.ByteString +type Rewrite = DynFlags -> Line -> Maybe Line +type LabRewrite = DynFlags -> ([Line], Line) -> Maybe Line -- XXX(kavon): debug only delete me later withComment :: String -> B.ByteString -> B.ByteString @@ -76,13 +79,13 @@ withComment com line = B.concat [B.pack $ wrap com, line] -- | This rewrite looks for return points of a llvm.cpscall and adds GC info -- above that label. -addInfoTable :: LabelMap ManglerStr -> Rewrite -addInfoTable info _ line = do +addInfoTable :: LabelMap ManglerStr -> LabRewrite +addInfoTable info _ (prevLabs, line) = do retPt <- B.stripPrefix labPrefix line (i, _) <- B.readInt retPt statics <- mapLookup (toKey i) info fullName <- B.stripSuffix colon line - return $ B.concat $ (map (\f -> f fullName) statics) ++ [line] + return $ B.concat $ (map (\f -> f fullName) statics) ++ prevLabs ++ [line] where -- TODO(kavon): check if prefix changes on different platforms. labPrefix = B.pack "L" @@ -91,19 +94,28 @@ addInfoTable info _ line = do -- | Rewrite a line of assembly source with the given rewrites, -- taking the first rewrite that applies for each kind of rewrite (label and non-label). -rewriteLine :: DynFlags -> [Rewrite] -> [Rewrite] -> B.ByteString -> B.ByteString -rewriteLine dflags labRewrites rewrites l = - case (maybNewSym, maybNewRest) of - (Nothing, Nothing) -> l -- avoid concat - (newS, newR) -> cat (fromMaybe symbol newS) (fromMaybe rest newR) +rewriteLine :: DynFlags -> [LabRewrite] -> [Rewrite] -> ([Line], Line) -> ([Line], Line) +rewriteLine dflags labRewrites rewrites (prevLabs, l) = + case (maybNewSym, maybNewRest, B.null rest) of + -- untouched line only has a label, collect it and emit nothing + (Nothing, Nothing, True) -> (l : prevLabs, B.empty) + -- a lab rewrite occurred, consuming the prevLabs in its result + (Just s, newR, _) -> ([], smush s (fromMaybe rest newR)) + -- the line did not only contain a label, and a label rewrite + -- hasn't occured, so we emit all collected labels + (Nothing, newR, _) -> ([], smush allLabs (fromMaybe rest newR)) + where + allLabs = revCat $ symbol : prevLabs where - cat sym rst = B.concat $ [sym, B.pack "\t", rst] + smush sym rst = B.concat $ [sym, B.pack "\t", rst] + + revCat ls = B.concat $ reverse ls findRwOf txt rws = firstJust $ map (\rw -> rw dflags txt) rws (symbol, rest) = splitLine l - maybNewSym = findRwOf symbol labRewrites -- check for new label part - maybNewRest = findRwOf rest rewrites -- check for new non-label part + maybNewSym = findRwOf (prevLabs, symbol) labRewrites -- check for new label part + maybNewRest = findRwOf rest rewrites -- check for new non-label part firstJust :: [Maybe a] -> Maybe a firstJust (jx@(Just _):_) = jx From git at git.haskell.org Tue Jun 27 09:16:57 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:16:57 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: revert changes to mangler in 0a0022517a189810d5904873151ffbc1964cc268 (e87a4d5) Message-ID: <20170627091657.DD1073A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/e87a4d5de7589817884f10b1753263e274ec5016/ghc >--------------------------------------------------------------- commit e87a4d5de7589817884f10b1753263e274ec5016 Author: Kavon Farvardin Date: Mon Jun 19 19:35:09 2017 +0100 revert changes to mangler in 0a0022517a189810d5904873151ffbc1964cc268 >--------------------------------------------------------------- e87a4d5de7589817884f10b1753263e274ec5016 compiler/llvmGen/LlvmMangler.hs | 50 ++++++++++++++++------------------------- 1 file changed, 19 insertions(+), 31 deletions(-) diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs index ee7b110..27f4a1f 100644 --- a/compiler/llvmGen/LlvmMangler.hs +++ b/compiler/llvmGen/LlvmMangler.hs @@ -43,20 +43,19 @@ llvmFixupAsm :: DynFlags -> LabelMap ManglerStr -> FilePath -> FilePath -> IO () llvmFixupAsm dflags gcInfo f1 f2 = {-# SCC "llvm_mangler" #-} withTiming (pure dflags) (text "LLVM Mangler") id $ withBinaryFile f1 ReadMode $ \r -> withBinaryFile f2 WriteMode $ \w -> do - go r w [] + go r w hClose r hClose w return () where - doRewrite x = rewriteLine dflags (labRewrites gcInfo) rewrites x + doRewrite a = rewriteLine dflags (labRewrites gcInfo) rewrites a - go :: Handle -> Handle -> [Line] -> IO () - go r w pL = do + go :: Handle -> Handle -> IO () + go r w = do e_l <- try $ B.hGetLine r ::IO (Either IOError B.ByteString) - let writeline x = B.hPutStrLn w newL >> go r w newPL - where (newPL, newL) = doRewrite x + let writeline a = B.hPutStrLn w (doRewrite a) >> go r w case e_l of - Right l -> writeline (pL, l) + Right l -> writeline l Left _ -> return () -- | These are the non-label rewrites that the mangler will perform @@ -64,12 +63,10 @@ rewrites :: [Rewrite] rewrites = [rewriteSymType, rewriteAVX] -- | These are the label-based rewrites that the mangler will perform -labRewrites :: LabelMap ManglerStr -> [LabRewrite] +labRewrites :: LabelMap ManglerStr -> [Rewrite] labRewrites info = [addInfoTable info] -type Line = B.ByteString -type Rewrite = DynFlags -> Line -> Maybe Line -type LabRewrite = DynFlags -> ([Line], Line) -> Maybe Line +type Rewrite = DynFlags -> B.ByteString -> Maybe B.ByteString -- XXX(kavon): debug only delete me later withComment :: String -> B.ByteString -> B.ByteString @@ -79,13 +76,13 @@ withComment com line = B.concat [B.pack $ wrap com, line] -- | This rewrite looks for return points of a llvm.cpscall and adds GC info -- above that label. -addInfoTable :: LabelMap ManglerStr -> LabRewrite -addInfoTable info _ (prevLabs, line) = do +addInfoTable :: LabelMap ManglerStr -> Rewrite +addInfoTable info _ line = do retPt <- B.stripPrefix labPrefix line (i, _) <- B.readInt retPt statics <- mapLookup (toKey i) info fullName <- B.stripSuffix colon line - return $ B.concat $ (map (\f -> f fullName) statics) ++ prevLabs ++ [line] + return $ B.concat $ (map (\f -> f fullName) statics) ++ [line] where -- TODO(kavon): check if prefix changes on different platforms. labPrefix = B.pack "L" @@ -94,28 +91,19 @@ addInfoTable info _ (prevLabs, line) = do -- | Rewrite a line of assembly source with the given rewrites, -- taking the first rewrite that applies for each kind of rewrite (label and non-label). -rewriteLine :: DynFlags -> [LabRewrite] -> [Rewrite] -> ([Line], Line) -> ([Line], Line) -rewriteLine dflags labRewrites rewrites (prevLabs, l) = - case (maybNewSym, maybNewRest, B.null rest) of - -- untouched line only has a label, collect it and emit nothing - (Nothing, Nothing, True) -> (l : prevLabs, B.empty) - -- a lab rewrite occurred, consuming the prevLabs in its result - (Just s, newR, _) -> ([], smush s (fromMaybe rest newR)) - -- the line did not only contain a label, and a label rewrite - -- hasn't occured, so we emit all collected labels - (Nothing, newR, _) -> ([], smush allLabs (fromMaybe rest newR)) - where - allLabs = revCat $ symbol : prevLabs +rewriteLine :: DynFlags -> [Rewrite] -> [Rewrite] -> B.ByteString -> B.ByteString +rewriteLine dflags labRewrites rewrites l = + case (maybNewSym, maybNewRest) of + (Nothing, Nothing) -> l -- avoid concat + (newS, newR) -> cat (fromMaybe symbol newS) (fromMaybe rest newR) where - smush sym rst = B.concat $ [sym, B.pack "\t", rst] - - revCat ls = B.concat $ reverse ls + cat sym rst = B.concat $ [sym, B.pack "\t", rst] findRwOf txt rws = firstJust $ map (\rw -> rw dflags txt) rws (symbol, rest) = splitLine l - maybNewSym = findRwOf (prevLabs, symbol) labRewrites -- check for new label part - maybNewRest = findRwOf rest rewrites -- check for new non-label part + maybNewSym = findRwOf symbol labRewrites -- check for new label part + maybNewRest = findRwOf rest rewrites -- check for new non-label part firstJust :: [Maybe a] -> Maybe a firstJust (jx@(Just _):_) = jx From git at git.haskell.org Tue Jun 27 09:17:00 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:17:00 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: fixing mangler issue that produced wrong RAs due to adjacent labels (027868b) Message-ID: <20170627091700.9C05B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/027868b8f240a6927ffe20f216ce194470872662/ghc >--------------------------------------------------------------- commit 027868b8f240a6927ffe20f216ce194470872662 Author: Kavon Farvardin Date: Tue Jun 20 18:27:13 2017 +0100 fixing mangler issue that produced wrong RAs due to adjacent labels >--------------------------------------------------------------- 027868b8f240a6927ffe20f216ce194470872662 compiler/llvmGen/LlvmMangler.hs | 60 +++++++++++++++++++++++++++-------------- 1 file changed, 40 insertions(+), 20 deletions(-) diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs index 27f4a1f..bf17e86 100644 --- a/compiler/llvmGen/LlvmMangler.hs +++ b/compiler/llvmGen/LlvmMangler.hs @@ -38,24 +38,31 @@ import Data.Maybe ( fromMaybe ) type ManglerStr = [B.ByteString -> B.ByteString] type ManglerInfo = Maybe (LabelMap ManglerStr) +-- to manage the simple state machine for adjacent labels +data State + = Default + | FirstLabel + | OtherLabel + -- | Read in assembly file and process llvmFixupAsm :: DynFlags -> LabelMap ManglerStr -> FilePath -> FilePath -> IO () llvmFixupAsm dflags gcInfo f1 f2 = {-# SCC "llvm_mangler" #-} withTiming (pure dflags) (text "LLVM Mangler") id $ withBinaryFile f1 ReadMode $ \r -> withBinaryFile f2 WriteMode $ \w -> do - go r w + go r w Default hClose r hClose w return () where - doRewrite a = rewriteLine dflags (labRewrites gcInfo) rewrites a + doRewrite = rewriteLine dflags (labRewrites gcInfo) rewrites - go :: Handle -> Handle -> IO () - go r w = do + go :: Handle -> Handle -> State -> IO () + go r w s = do e_l <- try $ B.hGetLine r ::IO (Either IOError B.ByteString) - let writeline a = B.hPutStrLn w (doRewrite a) >> go r w + let writeline a s = let (newL, newS) = doRewrite a s in + B.hPutStrLn w newL >> go r w newS case e_l of - Right l -> writeline l + Right l -> writeline l s Left _ -> return () -- | These are the non-label rewrites that the mangler will perform @@ -63,21 +70,16 @@ rewrites :: [Rewrite] rewrites = [rewriteSymType, rewriteAVX] -- | These are the label-based rewrites that the mangler will perform -labRewrites :: LabelMap ManglerStr -> [Rewrite] +labRewrites :: LabelMap ManglerStr -> [LabRewrite] labRewrites info = [addInfoTable info] type Rewrite = DynFlags -> B.ByteString -> Maybe B.ByteString - --- XXX(kavon): debug only delete me later -withComment :: String -> B.ByteString -> B.ByteString -withComment com line = B.concat [B.pack $ wrap com, line] - where - wrap c = "## comment -- " ++ c ++ "\n" +type LabRewrite = State -> Rewrite -- | This rewrite looks for return points of a llvm.cpscall and adds GC info -- above that label. -addInfoTable :: LabelMap ManglerStr -> Rewrite -addInfoTable info _ line = do +addInfoTable :: LabelMap ManglerStr -> LabRewrite +addInfoTable info FirstLabel _ line = do retPt <- B.stripPrefix labPrefix line (i, _) <- B.readInt retPt statics <- mapLookup (toKey i) info @@ -89,21 +91,35 @@ addInfoTable info _ line = do colon = B.pack ":" toKey = uniqueToLbl . intToUnique +addInfoTable _ _ _ _ = Nothing + -- | Rewrite a line of assembly source with the given rewrites, -- taking the first rewrite that applies for each kind of rewrite (label and non-label). -rewriteLine :: DynFlags -> [Rewrite] -> [Rewrite] -> B.ByteString -> B.ByteString -rewriteLine dflags labRewrites rewrites l = +rewriteLine :: DynFlags -> [LabRewrite] -> [Rewrite] -> B.ByteString -> State -> (B.ByteString, State) +rewriteLine dflags labRewrites rewrites l state = withState $ case (maybNewSym, maybNewRest) of (Nothing, Nothing) -> l -- avoid concat (newS, newR) -> cat (fromMaybe symbol newS) (fromMaybe rest newR) where + + -- the transition function of the state machine + withState l = (l, curState) + curState = case (isOnlyLabel split, state) of + (True, Default) -> FirstLabel + (True, FirstLabel) -> OtherLabel + (False, _) -> Default + _ -> state + cat sym rst = B.concat $ [sym, B.pack "\t", rst] + addState state rws = map (\rw -> rw state) rws findRwOf txt rws = firstJust $ map (\rw -> rw dflags txt) rws - (symbol, rest) = splitLine l - maybNewSym = findRwOf symbol labRewrites -- check for new label part - maybNewRest = findRwOf rest rewrites -- check for new non-label part + (split @ (symbol, rest)) = splitLine l + -- check for new label part + maybNewSym = findRwOf symbol $ addState curState labRewrites + -- check for new non-label part + maybNewRest = findRwOf rest rewrites firstJust :: [Maybe a] -> Maybe a firstJust (jx@(Just _):_) = jx @@ -167,3 +183,7 @@ splitLine l = (symbol, B.dropWhile isSpace rest) isSpace '\t' = True isSpace _ = False (symbol, rest) = B.span (not . isSpace) l + +isOnlyLabel :: (B.ByteString, B.ByteString) -> Bool +isOnlyLabel (symbol, rest) = + (B.null rest || B.head rest == '#') && not (B.null symbol) From git at git.haskell.org Tue Jun 27 09:17:03 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:17:03 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: reducing the degrees of freedom for debugging purposes (befcbd6) Message-ID: <20170627091703.535CC3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/befcbd6b23c5c827ba2e97a70f76b1db7c13b671/ghc >--------------------------------------------------------------- commit befcbd6b23c5c827ba2e97a70f76b1db7c13b671 Author: Kavon Farvardin Date: Wed Jun 21 17:45:50 2017 +0100 reducing the degrees of freedom for debugging purposes >--------------------------------------------------------------- befcbd6b23c5c827ba2e97a70f76b1db7c13b671 compiler/main/DriverPipeline.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 3935aad..ee0a031 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1424,7 +1424,7 @@ runPhase (RealPhase SplitAs) _input_fn dflags runPhase (RealPhaseWithInfo mangInfo LlvmOpt) input_fn dflags = do - let opt_lvl = max 0 (min 2 $ optLevel dflags) + let opt_lvl = max 0 (min 0 $ optLevel dflags) -- FIXME(kavon) change back to min 2 -- don't specify anything if user has specified commands. We do this -- for opt but not llc since opt is very specifically for optimisation -- passes only, so if the user is passing us extra options we assume @@ -1478,7 +1478,7 @@ runPhase (RealPhaseWithInfo mangInfo LlvmLlc) input_fn dflags output_fn <- phaseOutputFilename next_phase liftIO $ SysTools.runLlvmLlc dflags - ([ SysTools.Option (llvmOpts !! opt_lvl), + ([ -- FIXME(kavon) SysTools.Option (llvmOpts !! opt_lvl), SysTools.Option cpscall_workaround, SysTools.Option $ "-relocation-model=" ++ rmodel, SysTools.FileOption "" input_fn, From git at git.haskell.org Tue Jun 27 09:17:06 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:17:06 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: fixing #14 where D1 is returned but had no alloca in mandel (574bbff) Message-ID: <20170627091706.07AAD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/574bbff1618645a7a29d9f9025aebe4c1e9a8341/ghc >--------------------------------------------------------------- commit 574bbff1618645a7a29d9f9025aebe4c1e9a8341 Author: Kavon Farvardin Date: Fri Jun 23 17:15:24 2017 +0100 fixing #14 where D1 is returned but had no alloca in mandel >--------------------------------------------------------------- 574bbff1618645a7a29d9f9025aebe4c1e9a8341 compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 15 ++++++++++++--- 1 file changed, 12 insertions(+), 3 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index ab09516..328f89b 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -1788,7 +1788,7 @@ genLit _ CmmHighStackMark -- save a few lines in the output and hopefully speed compilation up a -- bit. -- --- FIXME(kavon): it seems inefficient to scan the whole function for reg assigns, +-- FIXME(kavon): it seems inefficient to scan the whole function for reg overwrites, -- we could instead update a map of CmmRegs -> LlvmVars when we see assignments during -- translation of a function's blocks, and then prepend the allocas to the entry block -- once we're done. @@ -1798,11 +1798,20 @@ 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 + -- Foreign 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 _ = [] - getRegsBlock (_, body, _) = concatMap getAssignedRegs $ blockToList body + + getTailRegs :: CmmNode O C -> [CmmReg] + -- When a native call returns, we reassign the values returned. See `doReturnTo` + getTailRegs (CmmCall {cml_cont = Just _, cml_ret_regs = regs}) = map CmmGlobal regs + getTailRegs _ = [] + + getRegsBlock (_, body, tl) = tailRegs ++ bodyRegs + where + tailRegs = getTailRegs tl + bodyRegs = concatMap getAssignedRegs $ blockToList body -- because we emit non-tail calls, the pinned registers such as the BasePtr is -- returned and we need to use an alloca for it. -kavon From git at git.haskell.org Tue Jun 27 09:17:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 09:17:08 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: NFC to test ssh key (c6c1728) Message-ID: <20170627091708.AED683A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/c6c172818a555aef09edb99ac8fae1a05b49df47/ghc >--------------------------------------------------------------- commit c6c172818a555aef09edb99ac8fae1a05b49df47 Author: Kavon Farvardin Date: Mon Jun 26 15:52:56 2017 +0100 NFC to test ssh key >--------------------------------------------------------------- c6c172818a555aef09edb99ac8fae1a05b49df47 compiler/llvmGen/LlvmMangler.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs index bf17e86..0517dde 100644 --- a/compiler/llvmGen/LlvmMangler.hs +++ b/compiler/llvmGen/LlvmMangler.hs @@ -95,7 +95,8 @@ addInfoTable _ _ _ _ = Nothing -- | Rewrite a line of assembly source with the given rewrites, -- taking the first rewrite that applies for each kind of rewrite (label and non-label). -rewriteLine :: DynFlags -> [LabRewrite] -> [Rewrite] -> B.ByteString -> State -> (B.ByteString, State) +rewriteLine :: DynFlags -> [LabRewrite] -> [Rewrite] + -> B.ByteString -> State -> (B.ByteString, State) rewriteLine dflags labRewrites rewrites l state = withState $ case (maybNewSym, maybNewRest) of (Nothing, Nothing) -> l -- avoid concat From git at git.haskell.org Tue Jun 27 10:29:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 10:29:08 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: updating submodules (1ebe453) Message-ID: <20170627102908.CBA743A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/1ebe45339f277b579e184264a6bd99ea24f74201/ghc >--------------------------------------------------------------- commit 1ebe45339f277b579e184264a6bd99ea24f74201 Author: Kavon Farvardin Date: Tue Jun 27 11:17:52 2017 +0100 updating submodules >--------------------------------------------------------------- 1ebe45339f277b579e184264a6bd99ea24f74201 libraries/Cabal | 2 +- libraries/hpc | 2 +- libraries/unix | 2 +- nofib | 2 +- utils/haddock | 2 +- 5 files changed, 5 insertions(+), 5 deletions(-) diff --git a/libraries/Cabal b/libraries/Cabal index 41f416b..ece0273 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 41f416bc27796a3dc87037b66b6fef6f5810bc77 +Subproject commit ece0273b48b7ff19fff6cd82913717d86d3ffbfa diff --git a/libraries/hpc b/libraries/hpc index b28546c..1544cf0 160000 --- a/libraries/hpc +++ b/libraries/hpc @@ -1 +1 @@ -Subproject commit b28546ca003c6dbff586609a093e8c8091c34b14 +Subproject commit 1544cf04c38ab3b613dba1e0737de49c33321655 diff --git a/libraries/unix b/libraries/unix index 19aaa0f..eb5fc94 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit 19aaa0fcca3427e4006a967972eb16a570ca43b1 +Subproject commit eb5fc942f8f570e754bba0f57a8fdaec3400194f diff --git a/nofib b/nofib index 7d7bc03..eccf532 160000 --- a/nofib +++ b/nofib @@ -1 +1 @@ -Subproject commit 7d7bc03c385022c36c557be77c79c107633b4454 +Subproject commit eccf532410eee45f30c07f389f7029871fd603db diff --git a/utils/haddock b/utils/haddock index a0c4790..a9f774f 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit a0c4790e15a2d3fab8d830eee8fcd639fe6d39c9 +Subproject commit a9f774fa3c12f9b8e093e46d58e7872d3d478951 From git at git.haskell.org Tue Jun 27 10:29:12 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 10:29:12 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: Merge branch 'master' into wip/kavon-nosplit-llvm (6851111) Message-ID: <20170627102912.6FAD03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/6851111def0361631a1e35630bb465c136112ce8/ghc >--------------------------------------------------------------- commit 6851111def0361631a1e35630bb465c136112ce8 Merge: 1ebe453 86abe0e Author: Kavon Farvardin Date: Tue Jun 27 11:28:29 2017 +0100 Merge branch 'master' into wip/kavon-nosplit-llvm >--------------------------------------------------------------- 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 6851111def0361631a1e35630bb465c136112ce8 From git at git.haskell.org Tue Jun 27 10:29:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 10:29:15 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm's head updated: Merge branch 'master' into wip/kavon-nosplit-llvm (6851111) Message-ID: <20170627102915.8A8323A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/kavon-nosplit-llvm' now includes: 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 1ebe453 updating submodules 6851111 Merge branch 'master' into wip/kavon-nosplit-llvm From git at git.haskell.org Tue Jun 27 15:29:31 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 15:29:31 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: import fixes for Hoopl (23a6940) Message-ID: <20170627152931.966F03A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/23a694038d4871eb5b6fa5664e0536b9bc468883/ghc >--------------------------------------------------------------- commit 23a694038d4871eb5b6fa5664e0536b9bc468883 Author: Kavon Farvardin Date: Tue Jun 27 16:29:08 2017 +0100 import fixes for Hoopl >--------------------------------------------------------------- 23a694038d4871eb5b6fa5664e0536b9bc468883 compiler/ghc.mk | 3 +++ compiler/llvmGen/LlvmCodeGen.hs | 1 + compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 1 + compiler/llvmGen/LlvmMangler.hs | 5 +++-- 4 files changed, 8 insertions(+), 2 deletions(-) diff --git a/compiler/ghc.mk b/compiler/ghc.mk index 34671f4..a83fa54 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -493,6 +493,9 @@ compiler_stage2_dll0_MODULES = \ PlaceHolder \ HsExtension \ PmExpr \ + Hoopl.Collections \ + Hoopl.Label \ + Hoopl.Unique \ HsPat \ HsSyn \ HsTypes \ diff --git a/compiler/llvmGen/LlvmCodeGen.hs b/compiler/llvmGen/LlvmCodeGen.hs index be8c688..16f5611 100644 --- a/compiler/llvmGen/LlvmCodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen.hs @@ -21,6 +21,7 @@ import Cmm import CmmUtils import Hoopl.Block import Hoopl.Collections +import Hoopl.Label import PprCmm import BufWrite diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index fb9aed8..6d1ab2b 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -21,6 +21,7 @@ import CmmSwitch import Hoopl.Block import Hoopl.Graph import Hoopl.Collections +import Hoopl.Label import DynFlags import FastString diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs index 0517dde..a21b135 100644 --- a/compiler/llvmGen/LlvmMangler.hs +++ b/compiler/llvmGen/LlvmMangler.hs @@ -19,8 +19,9 @@ import Outputable ( text ) import Control.Exception import qualified Data.ByteString.Char8 as B import System.IO -import Compiler.Hoopl -import Compiler.Hoopl.Internals ( uniqueToLbl ) +import Hoopl.Label +import Hoopl.Collections +import Hoopl.Unique ( intToUnique ) import Data.Maybe ( fromMaybe ) -- note [mangler string func] From git at git.haskell.org Tue Jun 27 17:34:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 17:34:43 +0000 (UTC) Subject: [commit: ghc] master: base/inputReady: Whitespace cleanup (b8f8736) Message-ID: <20170627173443.40E2B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b8f87363cfc6ddeacc67d99a79e316980ffd1f5c/ghc >--------------------------------------------------------------- commit b8f87363cfc6ddeacc67d99a79e316980ffd1f5c Author: Ben Gamari Date: Tue Jun 27 10:22:49 2017 -0400 base/inputReady: Whitespace cleanup >--------------------------------------------------------------- b8f87363cfc6ddeacc67d99a79e316980ffd1f5c libraries/base/cbits/inputReady.c | 162 +++++++++++++++++++------------------- 1 file changed, 81 insertions(+), 81 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 b8f87363cfc6ddeacc67d99a79e316980ffd1f5c From git at git.haskell.org Tue Jun 27 17:34:45 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 17:34:45 +0000 (UTC) Subject: [commit: ghc] master: Update docs to reflect changes to DeriveDataTypeable (914962c) Message-ID: <20170627173445.F3B073A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/914962ca23e407efdd3429dc89adcca7bee15f28/ghc >--------------------------------------------------------------- commit 914962ca23e407efdd3429dc89adcca7bee15f28 Author: Chris Martin Date: Mon Jun 26 14:55:15 2017 -0400 Update docs to reflect changes to DeriveDataTypeable >--------------------------------------------------------------- 914962ca23e407efdd3429dc89adcca7bee15f28 docs/users_guide/extending_ghc.rst | 2 +- docs/users_guide/glasgow_exts.rst | 21 ++++++++++++--------- docs/users_guide/safe_haskell.rst | 5 ----- 3 files changed, 13 insertions(+), 15 deletions(-) diff --git a/docs/users_guide/extending_ghc.rst b/docs/users_guide/extending_ghc.rst index 10c1b3d..a7fb538 100644 --- a/docs/users_guide/extending_ghc.rst +++ b/docs/users_guide/extending_ghc.rst @@ -425,7 +425,7 @@ will print out the name of any top-level non-recursive binding with the import Control.Monad (unless) import Data.Data - data SomeAnn = SomeAnn deriving (Data, Typeable) + data SomeAnn = SomeAnn deriving Data plugin :: Plugin plugin = defaultPlugin { diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 4a4f363..4d8b9ad 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -3590,8 +3590,7 @@ automatically derived: ``Functor``, defined in ``GHC.Base``. See :ref:`deriving-functor`. - With :ghc-flag:`-XDeriveDataTypeable`, you can derive instances of the class - ``Data``, defined in ``Data.Data``. See :ref:`deriving-typeable` for - deriving ``Typeable``. + ``Data``, defined in ``Data.Data``. See :ref:`deriving-data`. - With :ghc-flag:`-XDeriveFoldable`, you can derive instances of the class ``Foldable``, defined in ``Data.Foldable``. See @@ -4001,14 +4000,19 @@ For a full specification of the algorithms used in :ghc-flag:`-XDeriveFunctor`, :ghc-flag:`-XDeriveFoldable`, and :ghc-flag:`-XDeriveTraversable`, see :ghc-wiki:`this wiki page `. -.. _deriving-typeable: +.. _deriving-data: -Deriving ``Typeable`` instances +Deriving ``Data`` instances ------------------------------- .. ghc-flag:: -XDeriveDataTypeable - Enable automatic deriving of instances for the ``Typeable`` typeclass + Enable automatic deriving of instances for the ``Data`` typeclass + +.. _deriving-typeable: + +Deriving ``Typeable`` instances +------------------------------- The class ``Typeable`` is very special: @@ -4019,8 +4023,9 @@ The class ``Typeable`` is very special: ensures that the programmer cannot subvert the type system by writing bogus instances. -- Derived instances of ``Typeable`` are ignored, and may be reported as - an error in a later version of the compiler. +- Derived instances of ``Typeable`` may be declared if the + :ghc-flag:`-XDeriveDataTypeable` extension is enabled, but they are ignored, + and they may be reported as an error in a later version of the compiler. - The rules for solving \`Typeable\` constraints are as follows: @@ -12450,7 +12455,6 @@ That being said, with the appropriate use of wrapper datatypes, the above limitations induce no loss of generality: :: {-# LANGUAGE ConstraintKinds #-} - {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE StandaloneDeriving #-} @@ -12461,7 +12465,6 @@ above limitations induce no loss of generality: :: import GHC.StaticPtr data Dict c = c => Dict - deriving Typeable g1 :: Typeable a => StaticPtr (Dict (Show a) -> a -> String) g1 = static (\Dict -> show) diff --git a/docs/users_guide/safe_haskell.rst b/docs/users_guide/safe_haskell.rst index 5193f06..cdd5228 100644 --- a/docs/users_guide/safe_haskell.rst +++ b/docs/users_guide/safe_haskell.rst @@ -273,11 +273,6 @@ Furthermore, we restrict the following features: this reason, the ``Data.Coerce`` module is also considered unsafe. We are hoping to find a better solution here in the future. -- ``Data.Typeable`` — Hand crafted instances of the Typeable type class are not allowed - in Safe Haskell as this can easily be abused to unsafely coerce - between types. Derived instances (through the :ghc-flag:`-XDeriveDataTypeable` - extension) are still allowed. - - ``GHC.Generics`` — Hand crafted instances of the ``Generic`` type class are not allowed in Safe Haskell. Such instances aren't strictly unsafe, but there is an important invariant that a ``Generic`` instance should adhere to From git at git.haskell.org Tue Jun 27 17:34:48 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 17:34:48 +0000 (UTC) Subject: [commit: ghc] master: typecheck: Consider types containing coercions non-Typeable (1346525) Message-ID: <20170627173448.ABA873A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/134652542923e432bffb9fafe87893d785a17aae/ghc >--------------------------------------------------------------- commit 134652542923e432bffb9fafe87893d785a17aae Author: Ben Gamari Date: Tue Jun 27 10:29:33 2017 -0400 typecheck: Consider types containing coercions non-Typeable This was previously a panic and caused #13871. I believe just saying these types simply aren't Typeable should be correct. Test Plan: Validate, check `T13871` Reviewers: goldfire, austin Subscribers: rwbarton, thomie, RyanGlScott GHC Trac Issues: #13871 Differential Revision: https://phabricator.haskell.org/D3672 >--------------------------------------------------------------- 134652542923e432bffb9fafe87893d785a17aae compiler/typecheck/TcTypeable.hs | 2 +- testsuite/tests/typecheck/should_compile/all.T | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index 64db97c..e7a427f 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -439,7 +439,7 @@ typeIsTypeable (TyConApp tc args) = tyConIsTypeable tc typeIsTypeable (ForAllTy{}) = False typeIsTypeable (LitTy _) = True typeIsTypeable (CastTy{}) = False -typeIsTypeable (CoercionTy{}) = panic "typeIsTypeable(Coercion)" +typeIsTypeable (CoercionTy{}) = False -- | Maps kinds to 'KindRep' bindings. This binding may either be defined in -- some other module (in which case the @Maybe (LHsExpr Id@ will be 'Nothing') diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 5c3b323..72d33c1 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -564,4 +564,4 @@ test('T13651', normal, compile, ['']) test('T13785', normal, compile, ['']) test('T13804', normal, compile, ['']) test('T13822', normal, compile, ['']) -test('T13871', expect_broken(13871), compile, ['']) +test('T13871', normal, compile, ['']) From git at git.haskell.org Tue Jun 27 17:34:51 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 17:34:51 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add broken test for #13871 (12a3c39) Message-ID: <20170627173451.E95423A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/12a3c394b12e5e07314895e6c419f4f4031ad3a9/ghc >--------------------------------------------------------------- commit 12a3c394b12e5e07314895e6c419f4f4031ad3a9 Author: Ben Gamari Date: Tue Jun 27 10:29:23 2017 -0400 testsuite: Add broken test for #13871 Test Plan: Validate Reviewers: austin Subscribers: rwbarton, thomie, RyanGlScott GHC Trac Issues: #13871 Differential Revision: https://phabricator.haskell.org/D3671 >--------------------------------------------------------------- 12a3c394b12e5e07314895e6c419f4f4031ad3a9 testsuite/tests/typecheck/should_compile/T13871.hs | 15 +++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 16 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T13871.hs b/testsuite/tests/typecheck/should_compile/T13871.hs new file mode 100644 index 0000000..319d949 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13871.hs @@ -0,0 +1,15 @@ +{-# LANGUAGE ConstraintKinds #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeInType #-} +{-# LANGUAGE TypeOperators #-} +module Foo where + +import Data.Kind + +data Foo (a :: Type) (b :: Type) where + MkFoo :: (a ~ Int, b ~ Char) => Foo a b + +data family Sing (a :: k) +data SFoo (z :: Foo a b) where + SMkFoo :: SFoo MkFoo diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index b267819..5c3b323 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -564,3 +564,4 @@ test('T13651', normal, compile, ['']) test('T13785', normal, compile, ['']) test('T13804', normal, compile, ['']) test('T13822', normal, compile, ['']) +test('T13871', expect_broken(13871), compile, ['']) From git at git.haskell.org Tue Jun 27 17:34:55 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 17:34:55 +0000 (UTC) Subject: [commit: ghc] master: Allow bytecode interpreter to make unsafe foreign calls (9ef909d) Message-ID: <20170627173455.D9DF23A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9ef909db5ed3dc45fc1acdb608ad3f1896362966/ghc >--------------------------------------------------------------- commit 9ef909db5ed3dc45fc1acdb608ad3f1896362966 Author: Ben Gamari Date: Tue Jun 27 10:26:01 2017 -0400 Allow bytecode interpreter to make unsafe foreign calls Reviewers: austin, hvr, erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #8281, #13730. Differential Revision: https://phabricator.haskell.org/D3619 >--------------------------------------------------------------- 9ef909db5ed3dc45fc1acdb608ad3f1896362966 compiler/ghci/ByteCodeGen.hs | 8 ++++++-- compiler/ghci/ByteCodeInstr.hs | 15 ++++++++++----- rts/Interpreter.c | 16 +++++++++++----- testsuite/tests/ffi/should_fail/Makefile | 5 +++++ testsuite/tests/ffi/should_fail/UnsafeReenter.hs | 19 +++++++++++++++++++ testsuite/tests/ffi/should_fail/UnsafeReenter.stderr | 2 ++ testsuite/tests/ffi/should_fail/UnsafeReenter.stdout | 1 + testsuite/tests/ffi/should_fail/UnsafeReenterC.c | 6 ++++++ testsuite/tests/ffi/should_fail/all.T | 6 +++++- 9 files changed, 65 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 9ef909db5ed3dc45fc1acdb608ad3f1896362966 From git at git.haskell.org Tue Jun 27 17:34:58 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 17:34:58 +0000 (UTC) Subject: [commit: ghc] master: rts: Clarify whitehole logic in threadPaused (1e47126) Message-ID: <20170627173458.8FD093A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1e471265c1ea9b2c4e9709adc182c36d0635f071/ghc >--------------------------------------------------------------- commit 1e471265c1ea9b2c4e9709adc182c36d0635f071 Author: Ben Gamari Date: Tue Jun 27 10:30:00 2017 -0400 rts: Clarify whitehole logic in threadPaused Previously we would look at the indirectee field of a WHITEHOLE object. However, WHITEHOLE isn't a sort of indirection and therefore has no indirectee field. I encountered this while investigating #13615, although it doesn't fix that bug. Test Plan: Validate Reviewers: simonmar, austin, erikd Subscribers: rwbarton, thomie GHC Trac Issues: #13615 Differential Revision: https://phabricator.haskell.org/D3674 >--------------------------------------------------------------- 1e471265c1ea9b2c4e9709adc182c36d0635f071 rts/ThreadPaused.c | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/rts/ThreadPaused.c b/rts/ThreadPaused.c index 4ebc632..2483466 100644 --- a/rts/ThreadPaused.c +++ b/rts/ThreadPaused.c @@ -275,10 +275,9 @@ threadPaused(Capability *cap, StgTSO *tso) // deadlocked on itself. See #5226 for an instance of // this bug. // - if ((bh_info == &stg_WHITEHOLE_info || - bh_info == &stg_BLACKHOLE_info) - && - ((StgInd*)bh)->indirectee != (StgClosure*)tso) + if (((bh_info == &stg_BLACKHOLE_info) + && ((StgInd*)bh)->indirectee != (StgClosure*)tso) + || (bh_info == &stg_WHITEHOLE_info)) { debugTrace(DEBUG_squeeze, "suspending duplicate work: %ld words of stack", From git at git.haskell.org Tue Jun 27 17:35:01 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 17:35:01 +0000 (UTC) Subject: [commit: ghc] master: Treat banged bindings as FunBinds (6567c81) Message-ID: <20170627173501.5D53B3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6567c815135e93f8550d526f81d13f31c0cd92b6/ghc >--------------------------------------------------------------- commit 6567c815135e93f8550d526f81d13f31c0cd92b6 Author: Ben Gamari Date: Tue Jun 27 10:30:20 2017 -0400 Treat banged bindings as FunBinds This is another attempt at resolving #13594 by treating strict variable binds as FunBinds instead of PatBinds (as suggested in comment:1). Test Plan: Validate Reviewers: austin, alanz Subscribers: rwbarton, thomie, mpickering GHC Trac Issues: #13594 Differential Revision: https://phabricator.haskell.org/D3670 >--------------------------------------------------------------- 6567c815135e93f8550d526f81d13f31c0cd92b6 compiler/deSugar/Check.hs | 6 ++-- compiler/deSugar/DsBinds.hs | 29 ++++++++++------ compiler/deSugar/DsUtils.hs | 14 +++++++- compiler/deSugar/Match.hs | 9 +++-- compiler/hsSyn/HsBinds.hs | 40 ++++++++++++++++++++-- compiler/hsSyn/HsExpr.hs | 28 ++++++++++----- compiler/hsSyn/HsUtils.hs | 15 ++++++-- compiler/parser/Parser.y | 34 +++++++++++------- compiler/parser/RdrHsSyn.hs | 22 ++++++++---- compiler/rename/RnBinds.hs | 4 +-- compiler/typecheck/TcMatches.hs | 9 ++++- testsuite/tests/ghc-api/annotations/T10358.stdout | 6 ++-- .../parser/should_compile/DumpParsedAst.stderr | 3 +- .../parser/should_compile/DumpRenamedAst.stderr | 3 +- .../should_compile/DumpTypecheckedAst.stderr | 3 +- testsuite/tests/perf/compiler/all.T | 4 ++- testsuite/tests/typecheck/should_compile/all.T | 2 +- testsuite/tests/typecheck/should_run/all.T | 2 +- 18 files changed, 172 insertions(+), 61 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 6567c815135e93f8550d526f81d13f31c0cd92b6 From git at git.haskell.org Tue Jun 27 17:35:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 17:35:04 +0000 (UTC) Subject: [commit: ghc] master: Make module membership on ModuleGraph faster (b070858) Message-ID: <20170627173504.2E3093A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b0708588e87554899c2efc80a2d3eba353dbe926/ghc >--------------------------------------------------------------- commit b0708588e87554899c2efc80a2d3eba353dbe926 Author: Bartosz Nitka Date: Tue Jun 27 12:55:17 2017 -0400 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: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3646 >--------------------------------------------------------------- b0708588e87554899c2efc80a2d3eba353dbe926 compiler/backpack/DriverBkp.hs | 5 +- compiler/main/DriverMkDepend.hs | 16 ++-- compiler/main/DriverPipeline.hs | 5 +- compiler/main/GHC.hs | 23 ++--- compiler/main/GhcMake.hs | 54 ++++++----- compiler/main/HscMain.hs | 2 +- compiler/main/HscTypes.hs | 123 ++++++++++++++++++++++++-- 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 +- 13 files changed, 200 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 b0708588e87554899c2efc80a2d3eba353dbe926 From git at git.haskell.org Tue Jun 27 17:37:04 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 17:37:04 +0000 (UTC) Subject: [commit: ghc] master: Revert "Make module membership on ModuleGraph faster" (22b917e) Message-ID: <20170627173704.A25903A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/22b917eeb1d101cf0b6af2c94826446e4e2f2cdb/ghc >--------------------------------------------------------------- commit 22b917eeb1d101cf0b6af2c94826446e4e2f2cdb Author: Ben Gamari Date: Tue Jun 27 13:36:29 2017 -0400 Revert "Make module membership on ModuleGraph faster" I had not intended on merging this. This reverts commit b0708588e87554899c2efc80a2d3eba353dbe926. >--------------------------------------------------------------- 22b917eeb1d101cf0b6af2c94826446e4e2f2cdb compiler/backpack/DriverBkp.hs | 5 +- compiler/main/DriverMkDepend.hs | 16 ++-- compiler/main/DriverPipeline.hs | 5 +- compiler/main/GHC.hs | 23 +++-- compiler/main/GhcMake.hs | 54 +++++------ compiler/main/HscMain.hs | 2 +- compiler/main/HscTypes.hs | 123 ++------------------------ 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 +- 13 files changed, 75 insertions(+), 200 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 22b917eeb1d101cf0b6af2c94826446e4e2f2cdb From git at git.haskell.org Tue Jun 27 21:32:22 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jun 2017 21:32:22 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Various accumulated fixes (9d7b373) Message-ID: <20170627213222.C487F3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/9d7b373c6ce505d16da130d5be103b9423712003/ghc >--------------------------------------------------------------- commit 9d7b373c6ce505d16da130d5be103b9423712003 Author: Ben Gamari Date: Tue Jun 27 17:31:58 2017 -0400 Various accumulated fixes >--------------------------------------------------------------- 9d7b373c6ce505d16da130d5be103b9423712003 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 Wed Jun 28 01:40:28 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Jun 2017 01:40:28 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Don't use deleteDir (1cf836f) Message-ID: <20170628014028.1D7D73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/1cf836f7ee75bd40a89eb9e3f3ef29dcde4b7f97/ghc >--------------------------------------------------------------- commit 1cf836f7ee75bd40a89eb9e3f3ef29dcde4b7f97 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. >--------------------------------------------------------------- 1cf836f7ee75bd40a89eb9e3f3ef29dcde4b7f97 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 Wed Jun 28 03:01:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Jun 2017 03:01:10 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix testGhc (2f41a0b) Message-ID: <20170628030110.309F63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/2f41a0b68ecf4acf73651867f7070ffaa1962778/ghc >--------------------------------------------------------------- commit 2f41a0b68ecf4acf73651867f7070ffaa1962778 Author: Ben Gamari Date: Tue Jun 27 23:01:00 2017 -0400 Fix testGhc >--------------------------------------------------------------- 2f41a0b68ecf4acf73651867f7070ffaa1962778 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 Wed Jun 28 12:54:07 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Jun 2017 12:54:07 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Fix ghc path (836a591) Message-ID: <20170628125407.44A433A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/836a591f16ffa41804526afcf517f92288db7428/ghc >--------------------------------------------------------------- commit 836a591f16ffa41804526afcf517f92288db7428 Author: Ben Gamari Date: Wed Jun 28 08:53:54 2017 -0400 Fix ghc path >--------------------------------------------------------------- 836a591f16ffa41804526afcf517f92288db7428 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 Wed Jun 28 13:09:40 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Jun 2017 13:09:40 +0000 (UTC) Subject: [commit: ghc] master: Fix the in-scope set in TcHsType.instantiateTyN (4bdac33) Message-ID: <20170628130940.280FA3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4bdac331207e10650da9d3bf1b446bc8be3c069a/ghc >--------------------------------------------------------------- commit 4bdac331207e10650da9d3bf1b446bc8be3c069a Author: Simon Peyton Jones Date: Wed Jun 28 12:32:48 2017 +0100 Fix the in-scope set in TcHsType.instantiateTyN See Trac #13879 >--------------------------------------------------------------- 4bdac331207e10650da9d3bf1b446bc8be3c069a compiler/typecheck/TcHsType.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 46b306d..7c8a89a 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -929,11 +929,16 @@ instantiateTyN n ty ki num_to_inst = length bndrs - n -- NB: splitAt is forgiving with invalid numbers (inst_bndrs, leftover_bndrs) = splitAt num_to_inst bndrs + empty_subst = mkEmptyTCvSubst (mkInScopeSet (tyCoVarsOfType ki)) in if num_to_inst <= 0 then return (ty, ki) else - do { (subst, inst_args) <- tcInstBinders inst_bndrs + do { (subst, inst_args) <- tcInstBindersX 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 subst + , ppr rebuilt_ki + , ppr ki' ]) ; return (mkNakedAppTys ty inst_args, ki') } --------------------------- From git at git.haskell.org Wed Jun 28 13:09:42 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Jun 2017 13:09:42 +0000 (UTC) Subject: [commit: ghc] master: Do zonking in tcLHsKindSig (c80920d) Message-ID: <20170628130942.D802A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c80920d26f4eef8e87c130412d007628cff7589d/ghc >--------------------------------------------------------------- commit c80920d26f4eef8e87c130412d007628cff7589d Author: Simon Peyton Jones Date: Wed Jun 28 12:34:41 2017 +0100 Do zonking in tcLHsKindSig Trac #13879 showed that there was a missing zonk in tcLHsKind. I also renamed it to tcLHsKindSig, for consistency with type signatures There's a commment to explain why the zonk is needed. >--------------------------------------------------------------- c80920d26f4eef8e87c130412d007628cff7589d compiler/typecheck/TcHsType.hs | 20 ++++++++++++++------ compiler/typecheck/TcTyClsDecls.hs | 10 +++++----- 2 files changed, 19 insertions(+), 11 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 7c8a89a..601ebfc 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -37,7 +37,7 @@ module TcHsType ( kindGeneralize, -- Sort-checking kinds - tcLHsKind, + tcLHsKindSig, -- Pattern type signatures tcHsPatSigType, tcPatSig, funAppCtxt @@ -1428,7 +1428,7 @@ kcHsTyVarBndrs name unsat cusk open_fam all_kind_vars ; return tv_pair } kc_hs_tv (KindedTyVar (L _ name) lhs_kind) - = do { kind <- tcLHsKind lhs_kind + = do { kind <- tcLHsKindSig lhs_kind ; tcHsTyVarName (Just kind) name } report_non_cusk_tvs all_tvs @@ -1545,7 +1545,7 @@ tcHsTyVarBndr new_tv (UserTyVar (L _ name)) ; new_tv name kind } tcHsTyVarBndr new_tv (KindedTyVar (L _ name) kind) - = do { kind <- tcLHsKind kind + = do { kind <- tcLHsKindSig kind ; new_tv name kind } newWildTyVar :: Name -> TcM TcTyVar @@ -2031,12 +2031,20 @@ unifyKinds act_kinds * * ************************************************************************ -tcLHsKind converts a user-written kind to an internal, sort-checked kind. +tcLHsKindSig converts a user-written kind to an internal, sort-checked kind. It does sort checking and desugaring at the same time, in one single pass. -} -tcLHsKind :: LHsKind GhcRn -> TcM Kind -tcLHsKind = tc_lhs_kind kindLevelMode +tcLHsKindSig :: LHsKind GhcRn -> TcM Kind +tcLHsKindSig hs_kind + = do { kind <- tc_lhs_kind kindLevelMode hs_kind + ; zonkTcType kind } + -- This zonk is very important in the case of higher rank kinds + -- E.g. Trac #13879 f :: forall (p :: forall z (y::z). ). + -- + -- When instanting p's kind at occurrences of p in + -- it's crucial that the kind we instantiate is fully zonked, + -- else we may fail to substitute properly tc_lhs_kind :: TcTyMode -> LHsKind GhcRn -> TcM Kind tc_lhs_kind mode k diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index c8aca39..d253dc3 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -493,7 +493,7 @@ getInitialKind decl@(DataDecl { tcdLName = L _ name = do { (tycon, _) <- kcHsTyVarBndrs name True (hsDeclHasCusk decl) False True ktvs $ do { res_k <- case m_sig of - Just ksig -> tcLHsKind ksig + Just ksig -> tcLHsKindSig ksig Nothing -> return liftedTypeKind ; return (res_k, ()) } ; return (mkTcTyConEnv tycon) } @@ -508,7 +508,7 @@ getInitialKind decl@(SynDecl { tcdLName = L _ name False {- not open -} True ktvs $ do { res_k <- case kind_annotation rhs of Nothing -> newMetaKindVar - Just ksig -> tcLHsKind ksig + Just ksig -> tcLHsKindSig ksig ; return (res_k, ()) } ; return (mkTcTyConEnv tycon) } where @@ -536,8 +536,8 @@ getFamDeclInitialKind mb_cusk decl@(FamilyDecl { fdLName = L _ name = do { (tycon, _) <- kcHsTyVarBndrs name unsat cusk open True ktvs $ do { res_k <- case resultSig of - KindSig ki -> tcLHsKind ki - TyVarSig (L _ (KindedTyVar _ ki)) -> tcLHsKind ki + KindSig ki -> tcLHsKindSig ki + TyVarSig (L _ (KindedTyVar _ ki)) -> tcLHsKindSig ki _ -- open type families have * return kind by default | open -> return liftedTypeKind -- closed type families have their return kind inferred @@ -1191,7 +1191,7 @@ kcDataDefn fam_name (HsIB { hsib_body = pats }) ; discardResult $ case mb_kind of Nothing -> unifyKind (Just hs_ty_pats) res_k liftedTypeKind - Just k -> do { k' <- tcLHsKind k + Just k -> do { k' <- tcLHsKindSig k ; unifyKind (Just hs_ty_pats) res_k k' } } where hs_ty_pats = mkHsAppTys (noLoc $ HsTyVar NotPromoted (noLoc fam_name)) pats From git at git.haskell.org Wed Jun 28 13:09:46 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Jun 2017 13:09:46 +0000 (UTC) Subject: [commit: ghc] master: Fix constraint solving for forall-types (fae672f) Message-ID: <20170628130946.38CE73A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fae672f647fe00c303d8fb56971563c1a76ad04e/ghc >--------------------------------------------------------------- commit fae672f647fe00c303d8fb56971563c1a76ad04e Author: Simon Peyton Jones Date: Wed Jun 28 12:38:59 2017 +0100 Fix constraint solving for forall-types Trac #13879 showed that when we were trying to solve (forall z1 (y1::z1). ty1) ~ (forall z2 (y2:z2). ty2) we'd end up spitting out z1~z2 with no binding site for them. Those kind equalities need to be inside the implication. I ended up re-factoring the code for solving forall-equalities. It's quite nice now. >--------------------------------------------------------------- fae672f647fe00c303d8fb56971563c1a76ad04e compiler/typecheck/TcCanonical.hs | 95 ++++++++++++++++----- compiler/typecheck/TcSMonad.hs | 98 +++++++++++----------- testsuite/tests/typecheck/should_compile/T13879.hs | 29 +++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + .../tests/typecheck/should_fail/tcfail174.stderr | 2 +- 5 files changed, 152 insertions(+), 73 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fae672f647fe00c303d8fb56971563c1a76ad04e From git at git.haskell.org Wed Jun 28 13:47:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Jun 2017 13:47:36 +0000 (UTC) Subject: [commit: ghc] master: Zap stable unfoldings in worker/wrapper (87c5fdb) Message-ID: <20170628134736.A50503A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/87c5fdbba118db1938d699951a811cc2f6206d4d/ghc >--------------------------------------------------------------- commit 87c5fdbba118db1938d699951a811cc2f6206d4d Author: Simon Peyton Jones Date: Wed Jun 28 14:45:40 2017 +0100 Zap stable unfoldings in worker/wrapper This patch fixes the buglet described in Trac #13890. >--------------------------------------------------------------- 87c5fdbba118db1938d699951a811cc2f6206d4d compiler/basicTypes/Id.hs | 9 +++++++-- compiler/simplCore/Simplify.hs | 3 +-- compiler/stranal/WwLib.hs | 7 +++++-- 3 files changed, 13 insertions(+), 6 deletions(-) diff --git a/compiler/basicTypes/Id.hs b/compiler/basicTypes/Id.hs index 8a5e28a..290e262 100644 --- a/compiler/basicTypes/Id.hs +++ b/compiler/basicTypes/Id.hs @@ -53,7 +53,7 @@ module Id ( setIdInfo, lazySetIdInfo, modifyIdInfo, maybeModifyIdInfo, zapLamIdInfo, zapIdDemandInfo, zapIdUsageInfo, zapIdUsageEnvInfo, zapIdUsedOnceInfo, zapIdTailCallInfo, - zapFragileIdInfo, zapIdStrictness, + zapFragileIdInfo, zapIdStrictness, zapStableUnfolding, transferPolyIdInfo, -- ** Predicates on Ids @@ -117,7 +117,7 @@ module Id ( #include "HsVersions.h" import DynFlags -import CoreSyn ( CoreRule, evaldUnfolding, Unfolding( NoUnfolding ) ) +import CoreSyn ( CoreRule, isStableUnfolding, evaldUnfolding, Unfolding( NoUnfolding ) ) import IdInfo import BasicTypes @@ -867,6 +867,11 @@ zapIdUsedOnceInfo = zapInfo zapUsedOnceInfo zapIdTailCallInfo :: Id -> Id zapIdTailCallInfo = zapInfo zapTailCallInfo +zapStableUnfolding :: Id -> Id +zapStableUnfolding id + | isStableUnfolding (realIdUnfolding id) = setIdUnfolding id NoUnfolding + | otherwise = id + {- Note [transferPolyIdInfo] ~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index 1c5534f..8bccbfe 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -1519,8 +1519,7 @@ simplLam env (bndr:bndrs) body (ApplyToVal { sc_arg = arg, sc_env = arg_se ; simplNonRecE env zapped_bndr (arg, arg_se) (bndrs, body) cont } where zapped_bndr -- See Note [Zap unfolding when beta-reducing] - | isId bndr, isStableUnfolding (realIdUnfolding bndr) - = setIdUnfolding bndr NoUnfolding + | isId bndr = zapStableUnfolding bndr | otherwise = bndr -- discard a non-counting tick on a lambda. This may change the diff --git a/compiler/stranal/WwLib.hs b/compiler/stranal/WwLib.hs index 8d41426..f83aafe 100644 --- a/compiler/stranal/WwLib.hs +++ b/compiler/stranal/WwLib.hs @@ -587,8 +587,11 @@ mkWWstr_one dflags fam_envs arg ; let unpk_args = zipWith3 mk_ww_arg uniqs inst_con_arg_tys cs unbox_fn = mkUnpackCase (Var arg) co uniq1 data_con unpk_args - rebox_fn = Let (NonRec arg con_app) - con_app = mkConApp2 data_con inst_tys unpk_args `mkCast` mkSymCo co + arg_no_unf = zapStableUnfolding arg + -- See Note [Zap unfolding when beta-reducing] + -- in Simplify.hs; and see Trac #13890 + rebox_fn = Let (NonRec arg_no_unf con_app) + con_app = mkConApp2 data_con inst_tys unpk_args `mkCast` mkSymCo co ; (_, worker_args, wrap_fn, work_fn) <- mkWWstr dflags fam_envs unpk_args ; return (True, worker_args, unbox_fn . wrap_fn, work_fn . rebox_fn) } -- Don't pass the arg, rebox instead From git at git.haskell.org Wed Jun 28 14:41:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Jun 2017 14:41:29 +0000 (UTC) Subject: [commit: ghc] master: Typos in comments and manual [ci skip] (78c80c2) Message-ID: <20170628144129.B28EF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/78c80c250021ccb7a84afaabebe0d69f9b9372ee/ghc >--------------------------------------------------------------- commit 78c80c250021ccb7a84afaabebe0d69f9b9372ee Author: Gabor Greif Date: Wed Jun 28 16:40:45 2017 +0200 Typos in comments and manual [ci skip] >--------------------------------------------------------------- 78c80c250021ccb7a84afaabebe0d69f9b9372ee compiler/basicTypes/DataCon.hs | 2 +- compiler/coreSyn/CoreArity.hs | 2 +- compiler/main/DynFlags.hs | 2 +- compiler/typecheck/TcUnify.hs | 4 ++-- docs/users_guide/glasgow_exts.rst | 2 +- libraries/base/Control/Monad/ST/Lazy/Imp.hs | 2 +- testsuite/tests/indexed-types/should_fail/T4485.hs | 2 +- 7 files changed, 8 insertions(+), 8 deletions(-) diff --git a/compiler/basicTypes/DataCon.hs b/compiler/basicTypes/DataCon.hs index cc475e2..1629f36 100644 --- a/compiler/basicTypes/DataCon.hs +++ b/compiler/basicTypes/DataCon.hs @@ -1052,7 +1052,7 @@ dataConInstSig -> [Type] -- Instantiate the *universal* tyvars with these types -> ([TyVar], ThetaType, [Type]) -- Return instantiated existentials -- theta and arg tys --- ^ Instantantiate the universal tyvars of a data con, +-- ^ Instantiate the universal tyvars of a data con, -- returning the instantiated existentials, constraints, and args dataConInstSig (MkData { dcUnivTyVars = univ_tvs, dcExTyVars = ex_tvs , dcEqSpec = eq_spec, dcOtherTheta = theta diff --git a/compiler/coreSyn/CoreArity.hs b/compiler/coreSyn/CoreArity.hs index 3ab71d2..3f429d1 100644 --- a/compiler/coreSyn/CoreArity.hs +++ b/compiler/coreSyn/CoreArity.hs @@ -317,7 +317,7 @@ do so; it improves some programs significantly, and increasing convergence isn't a bad thing. Hence the ABot/ATop in ArityType. So these two transformations aren't always the Right Thing, and we -have several tickets reporting unexpected bahaviour resulting from +have several tickets reporting unexpected behaviour resulting from this transformation. So we try to limit it as much as possible: (1) Do NOT move a lambda outside a known-bottom case expression diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 366406e..dac3136 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -4100,7 +4100,7 @@ impliedXFlags -- * utils/mkUserGuidePart/Options/ -- * docs/users_guide/using.rst -- --- The first contains the Flag Refrence section, which breifly lists all +-- The first contains the Flag Reference section, which briefly lists all -- available flags. The second contains a detailed description of the -- flags. Both places should contain information whether a flag is implied by -- -O0, -O or -O2. diff --git a/compiler/typecheck/TcUnify.hs b/compiler/typecheck/TcUnify.hs index bfaacef..1cbf574 100644 --- a/compiler/typecheck/TcUnify.hs +++ b/compiler/typecheck/TcUnify.hs @@ -900,7 +900,7 @@ In some cases we want to deeply instantiate before filling in an InferResult, and in some cases not. That's why InferReult has the ir_inst flag. -* ir_inst = True: deeply instantantiate +* ir_inst = True: deeply instantiate Consider f x = (*) @@ -920,7 +920,7 @@ has the ir_inst flag. Here want to instantiate f's type so that the ?x::Int constraint gets discharged by the enclosing implicit-parameter binding. -* ir_inst = False: do not instantantiate +* ir_inst = False: do not instantiate Consider this (which uses visible type application): diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 4d8b9ad..d473841 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -12268,7 +12268,7 @@ If we did it in Haskell source, thus :: let f = ... in f `seq` body -then ``f``\ 's polymorphic type would get intantiated, so the Core +then ``f``\ 's polymorphic type would get instantiated, so the Core translation would be :: let f = ... in f Any `seq` body diff --git a/libraries/base/Control/Monad/ST/Lazy/Imp.hs b/libraries/base/Control/Monad/ST/Lazy/Imp.hs index 67d5838..4f1204b 100644 --- a/libraries/base/Control/Monad/ST/Lazy/Imp.hs +++ b/libraries/base/Control/Monad/ST/Lazy/Imp.hs @@ -51,7 +51,7 @@ import qualified Control.Monad.Fail as Fail -- by @s@, and returns a value of type @a at . -- The @s@ parameter is either -- --- * an unstantiated type variable (inside invocations of 'runST'), or +-- * an uninstantiated type variable (inside invocations of 'runST'), or -- -- * 'RealWorld' (inside invocations of 'stToIO'). -- diff --git a/testsuite/tests/indexed-types/should_fail/T4485.hs b/testsuite/tests/indexed-types/should_fail/T4485.hs index c3407cc..060e857 100644 --- a/testsuite/tests/indexed-types/should_fail/T4485.hs +++ b/testsuite/tests/indexed-types/should_fail/T4485.hs @@ -6,7 +6,7 @@ -- how to achieve something similar to the old behavior. This is -- preventing HSP (and by extension, happstack) from migrating to GHC -- 7. I reported this earlier on the mailing lists, but I have further --- simplied the test case here. +-- simplified the test case here. {-# LANGUAGE TypeFamilies, MultiParamTypeClasses , FlexibleContexts, FlexibleInstances, UndecidableInstances From git at git.haskell.org Wed Jun 28 18:13:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Jun 2017 18:13:02 +0000 (UTC) Subject: [commit: ghc] master: More typos in comments [ci skip] (3f9422c) Message-ID: <20170628181302.B56993A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3f9422cb68d564b4e79093532f5d293987d515bd/ghc >--------------------------------------------------------------- commit 3f9422cb68d564b4e79093532f5d293987d515bd Author: Gabor Greif Date: Wed Jun 28 17:15:23 2017 +0200 More typos in comments [ci skip] >--------------------------------------------------------------- 3f9422cb68d564b4e79093532f5d293987d515bd compiler/deSugar/DsBinds.hs | 2 +- compiler/hsSyn/HsLit.hs | 2 +- compiler/simplCore/simplifier.tib | 2 +- compiler/typecheck/TcHsType.hs | 2 +- compiler/typecheck/TcRnTypes.hs | 2 +- 5 files changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index f03f586..5d9a33d 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -429,7 +429,7 @@ Note [Rules and inlining] ~~~~~~~~~~~~~~~~~~~~~~~~~ Common special case: no type or dictionary abstraction This is a bit less trivial than you might suppose -The naive way woudl be to desguar to something like +The naive way would be to desugar to something like f_lcl = ...f_lcl... -- The "binds" from AbsBinds M.f = f_lcl -- Generated from "exports" But we don't want that, because if M.f isn't exported, diff --git a/compiler/hsSyn/HsLit.hs b/compiler/hsSyn/HsLit.hs index 46e5dd5a..1044f9b 100644 --- a/compiler/hsSyn/HsLit.hs +++ b/compiler/hsSyn/HsLit.hs @@ -161,7 +161,7 @@ This witness should replace the literal. This dual role is unusual, because we're replacing 'fromInteger' with a call to fromInteger. Reason: it allows commoning up of the fromInteger -calls, which wouldn't be possible if the desguarar made the application. +calls, which wouldn't be possible if the desugarer made the application. The PostTcType in each branch records the type the overload literal is found to have. diff --git a/compiler/simplCore/simplifier.tib b/compiler/simplCore/simplifier.tib index 5ffbefe..01919cd 100644 --- a/compiler/simplCore/simplifier.tib +++ b/compiler/simplCore/simplifier.tib @@ -482,7 +482,7 @@ generate code, something like this: if (y) {...code for E2...} l1: ...code for E1... @ -In our setting, here's what will happen. First we desguar the +In our setting, here's what will happen. First we desugar the conditional, and inline the definition of @||@: @ case (case x of {True -> True; False -> y}) of diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 601ebfc..1b4deec 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -2042,7 +2042,7 @@ tcLHsKindSig hs_kind -- This zonk is very important in the case of higher rank kinds -- E.g. Trac #13879 f :: forall (p :: forall z (y::z). ). -- - -- When instanting p's kind at occurrences of p in + -- When instantiating p's kind at occurrences of p in -- it's crucial that the kind we instantiate is fully zonked, -- else we may fail to substitute properly diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index ed435ed..3992a7e 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -385,7 +385,7 @@ data DsGblEnv -- iff '-fvectorise' flag was given as well as -- exported entities of 'Data.Array.Parallel' iff -- '-XParallelArrays' was given; otherwise, empty - , ds_parr_bi :: PArrBuiltin -- desugarar names for '-XParallelArrays' + , ds_parr_bi :: PArrBuiltin -- desugarer names for '-XParallelArrays' , ds_complete_matches :: CompleteMatchMap -- Additional complete pattern matches } From git at git.haskell.org Wed Jun 28 18:13:05 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Jun 2017 18:13:05 +0000 (UTC) Subject: [commit: ghc] master: Remove unneeded import (7097f94) Message-ID: <20170628181305.7251D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7097f94df0c6667be2343306ffcda152fa22abcf/ghc >--------------------------------------------------------------- commit 7097f94df0c6667be2343306ffcda152fa22abcf Author: Gabor Greif Date: Wed Jun 28 20:04:53 2017 +0200 Remove unneeded import This fails in stage 2 when bootstrapping HEAD with HEAD due to -Werror. Turns out that tcInstBinders is now dead, and I'll remove it if nobody protests. I'd like to hear opinions whether tcInstBindersX then should be renamed to tcInstBinders. >--------------------------------------------------------------- 7097f94df0c6667be2343306ffcda152fa22abcf compiler/typecheck/TcHsType.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 1b4deec..01cac59 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 ( tcInstBinders, tcInstBindersX, tcInstBinderX ) +import Inst ( tcInstBindersX, tcInstBinderX ) 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 tcInstBinders and tcInstBindersX. +again. This is done in calls to tcInstBindersX. 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 From git at git.haskell.org Thu Jun 29 11:07:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Jun 2017 11:07:13 +0000 (UTC) Subject: [commit: ghc] master: remove dead function 'tcInstBinders' (54ccf0c) Message-ID: <20170629110713.A4BBF3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/54ccf0c957a279c20e1a37a5a462612af8036739/ghc >--------------------------------------------------------------- commit 54ccf0c957a279c20e1a37a5a462612af8036739 Author: Gabor Greif Date: Thu Jun 29 10:20:11 2017 +0200 remove dead function 'tcInstBinders' >--------------------------------------------------------------- 54ccf0c957a279c20e1a37a5a462612af8036739 compiler/typecheck/Inst.hs | 7 +------ 1 file changed, 1 insertion(+), 6 deletions(-) diff --git a/compiler/typecheck/Inst.hs b/compiler/typecheck/Inst.hs index cad7793..093c004 100644 --- a/compiler/typecheck/Inst.hs +++ b/compiler/typecheck/Inst.hs @@ -15,7 +15,7 @@ module Inst ( instCall, instDFunType, instStupidTheta, newWanted, newWanteds, - tcInstBinders, tcInstBindersX, tcInstBinderX, + tcInstBindersX, tcInstBinderX, newOverloadedLit, mkOverLit, @@ -378,11 +378,6 @@ instStupidTheta orig theta --------------------------- -- | This is used to instantiate binders when type-checking *types* only. --- See also Note [Bidirectional type checking] -tcInstBinders :: [TyBinder] -> TcM (TCvSubst, [TcType]) -tcInstBinders = tcInstBindersX emptyTCvSubst Nothing - --- | 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) From git at git.haskell.org Thu Jun 29 12:58:15 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Jun 2017 12:58:15 +0000 (UTC) Subject: [commit: ghc] wip/jenkins: Properly quote instDir (751f422) Message-ID: <20170629125815.070113A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/jenkins Link : http://ghc.haskell.org/trac/ghc/changeset/751f422404ec38c1224eeae219378c5bcf9cc290/ghc >--------------------------------------------------------------- commit 751f422404ec38c1224eeae219378c5bcf9cc290 Author: Ben Gamari Date: Thu Jun 29 08:58:04 2017 -0400 Properly quote instDir >--------------------------------------------------------------- 751f422404ec38c1224eeae219378c5bcf9cc290 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 Jun 29 14:31:11 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Jun 2017 14:31:11 +0000 (UTC) Subject: [commit: ghc] master: Fix lexically-scoped type variables (3b0e755) Message-ID: <20170629143111.BED3C3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3b0e7555fafe73b157a96ca48d8ddc04ad81b231/ghc >--------------------------------------------------------------- commit 3b0e7555fafe73b157a96ca48d8ddc04ad81b231 Author: Simon Peyton Jones Date: Thu Jun 29 15:26:54 2017 +0100 Fix lexically-scoped type variables Trac #13881 showed that our handling of lexically scoped type variables was way off when we bring into scope a name 'y' for a pre-existing type variable 'a', perhaps with an entirely different name. This patch fixes it; see TcHsType Note [Pattern signature binders] >--------------------------------------------------------------- 3b0e7555fafe73b157a96ca48d8ddc04ad81b231 compiler/typecheck/TcHsType.hs | 80 +++++++++++++++------- compiler/typecheck/TcPat.hs | 4 +- compiler/typecheck/TcRules.hs | 4 +- testsuite/tests/typecheck/should_compile/T13881.hs | 17 +++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 5 files changed, 78 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 3b0e7555fafe73b157a96ca48d8ddc04ad81b231 From git at git.haskell.org Thu Jun 29 14:37:08 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Jun 2017 14:37:08 +0000 (UTC) Subject: [commit: ghc] master: Revert "Remove the Windows GCC driver." (58c781d) Message-ID: <20170629143708.3B7073A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/58c781da4861faab11e4c5804e07e6892908ef72/ghc >--------------------------------------------------------------- commit 58c781da4861faab11e4c5804e07e6892908ef72 Author: Simon Peyton Jones Date: Thu Jun 29 15:34:39 2017 +0100 Revert "Remove the Windows GCC driver." This reverts commit d6cecde585b0980ed8e0050c5a1d315789fb6356. The patch broke Simon PJ's Windows build, becuase he didn't have (and should not need) a separate msys2 gcc. Following an exchange on the ghc-devs list, Tamar wrote Oops, sorry, didn’t notice it because both mine and harbormaster’s msys2 have separate GCCs installed as well. I don’t see an easy fix that would also work for end user Configure based cabal installs. So I think I’ll have to go back to the drawing board for this one. You can just leave it reverted. >--------------------------------------------------------------- 58c781da4861faab11e4c5804e07e6892908ef72 aclocal.m4 | 3 +- compiler/main/SysTools.hs | 38 ++++++++--------------- configure.ac | 8 +++++ docs/users_guide/8.4.1-notes.rst | 3 -- driver/gcc/gcc.c | 66 ++++++++++++++++++++++++++++++++++++++++ 5 files changed, 88 insertions(+), 30 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 58c781da4861faab11e4c5804e07e6892908ef72 From git at git.haskell.org Thu Jun 29 16:48:43 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Jun 2017 16:48:43 +0000 (UTC) Subject: [commit: ghc] wip/kavon-nosplit-llvm: cpscall and shrink-wraping don't get along at the moment (d4c3662) Message-ID: <20170629164843.206093A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kavon-nosplit-llvm Link : http://ghc.haskell.org/trac/ghc/changeset/d4c36625529effd1ee3f806c29729933d14bd257/ghc >--------------------------------------------------------------- commit d4c36625529effd1ee3f806c29729933d14bd257 Author: Kavon Farvardin Date: Thu Jun 29 17:48:07 2017 +0100 cpscall and shrink-wraping don't get along at the moment >--------------------------------------------------------------- d4c36625529effd1ee3f806c29729933d14bd257 compiler/main/DriverPipeline.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index a34c5dc..f885424 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1493,8 +1493,8 @@ runPhase (RealPhaseWithInfo mangInfo LlvmLlc) input_fn dflags output_fn <- phaseOutputFilename next_phase liftIO $ SysTools.runLlvmLlc dflags - ([ -- FIXME(kavon) SysTools.Option (llvmOpts !! opt_lvl), - SysTools.Option cpscall_workaround, + ( map SysTools.Option cpscall_workaround + ++ [ -- FIXME(kavon) SysTools.Option (llvmOpts !! opt_lvl), SysTools.Option $ "-relocation-model=" ++ rmodel, SysTools.FileOption "" input_fn, SysTools.Option "-o", SysTools.FileOption "" output_fn] @@ -1518,7 +1518,7 @@ runPhase (RealPhaseWithInfo mangInfo LlvmLlc) input_fn dflags where -- TODO(kavon): temporary - cpscall_workaround = "-disable-machine-cse" + cpscall_workaround = ["-disable-machine-cse", "-enable-shrink-wrap=false"] -- Bug in LLVM at O3 on OSX. llvmOpts = if platformOS (targetPlatform dflags) == OSDarwin From git at git.haskell.org Thu Jun 29 17:54:10 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Jun 2017 17:54:10 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Update docs to reflect changes to DeriveDataTypeable (46d350d) Message-ID: <20170629175410.AF81D3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/46d350d2d60791af77d1f0763b61b0f710d9b664/ghc >--------------------------------------------------------------- commit 46d350d2d60791af77d1f0763b61b0f710d9b664 Author: Chris Martin Date: Mon Jun 26 14:55:15 2017 -0400 Update docs to reflect changes to DeriveDataTypeable (cherry picked from commit 914962ca23e407efdd3429dc89adcca7bee15f28) >--------------------------------------------------------------- 46d350d2d60791af77d1f0763b61b0f710d9b664 docs/users_guide/extending_ghc.rst | 2 +- docs/users_guide/glasgow_exts.rst | 21 ++++++++++++--------- docs/users_guide/safe_haskell.rst | 5 ----- 3 files changed, 13 insertions(+), 15 deletions(-) diff --git a/docs/users_guide/extending_ghc.rst b/docs/users_guide/extending_ghc.rst index 10c1b3d..a7fb538 100644 --- a/docs/users_guide/extending_ghc.rst +++ b/docs/users_guide/extending_ghc.rst @@ -425,7 +425,7 @@ will print out the name of any top-level non-recursive binding with the import Control.Monad (unless) import Data.Data - data SomeAnn = SomeAnn deriving (Data, Typeable) + data SomeAnn = SomeAnn deriving Data plugin :: Plugin plugin = defaultPlugin { diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index c738862..c116a5e 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -3590,8 +3590,7 @@ automatically derived: ``Functor``, defined in ``GHC.Base``. See :ref:`deriving-functor`. - With :ghc-flag:`-XDeriveDataTypeable`, you can derive instances of the class - ``Data``, defined in ``Data.Data``. See :ref:`deriving-typeable` for - deriving ``Typeable``. + ``Data``, defined in ``Data.Data``. See :ref:`deriving-data`. - With :ghc-flag:`-XDeriveFoldable`, you can derive instances of the class ``Foldable``, defined in ``Data.Foldable``. See @@ -3906,14 +3905,19 @@ For a full specification of the algorithms used in :ghc-flag:`-XDeriveFunctor`, :ghc-flag:`-XDeriveFoldable`, and :ghc-flag:`-XDeriveTraversable`, see :ghc-wiki:`this wiki page `. -.. _deriving-typeable: +.. _deriving-data: -Deriving ``Typeable`` instances +Deriving ``Data`` instances ------------------------------- .. ghc-flag:: -XDeriveDataTypeable - Enable automatic deriving of instances for the ``Typeable`` typeclass + Enable automatic deriving of instances for the ``Data`` typeclass + +.. _deriving-typeable: + +Deriving ``Typeable`` instances +------------------------------- The class ``Typeable`` is very special: @@ -3924,8 +3928,9 @@ The class ``Typeable`` is very special: ensures that the programmer cannot subvert the type system by writing bogus instances. -- Derived instances of ``Typeable`` are ignored, and may be reported as - an error in a later version of the compiler. +- Derived instances of ``Typeable`` may be declared if the + :ghc-flag:`-XDeriveDataTypeable` extension is enabled, but they are ignored, + and they may be reported as an error in a later version of the compiler. - The rules for solving \`Typeable\` constraints are as follows: @@ -12355,7 +12360,6 @@ That being said, with the appropriate use of wrapper datatypes, the above limitations induce no loss of generality: :: {-# LANGUAGE ConstraintKinds #-} - {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE StandaloneDeriving #-} @@ -12366,7 +12370,6 @@ above limitations induce no loss of generality: :: import GHC.StaticPtr data Dict c = c => Dict - deriving Typeable g1 :: Typeable a => StaticPtr (Dict (Show a) -> a -> String) g1 = static (\Dict -> show) diff --git a/docs/users_guide/safe_haskell.rst b/docs/users_guide/safe_haskell.rst index 5193f06..cdd5228 100644 --- a/docs/users_guide/safe_haskell.rst +++ b/docs/users_guide/safe_haskell.rst @@ -273,11 +273,6 @@ Furthermore, we restrict the following features: this reason, the ``Data.Coerce`` module is also considered unsafe. We are hoping to find a better solution here in the future. -- ``Data.Typeable`` — Hand crafted instances of the Typeable type class are not allowed - in Safe Haskell as this can easily be abused to unsafely coerce - between types. Derived instances (through the :ghc-flag:`-XDeriveDataTypeable` - extension) are still allowed. - - ``GHC.Generics`` — Hand crafted instances of the ``Generic`` type class are not allowed in Safe Haskell. Such instances aren't strictly unsafe, but there is an important invariant that a ``Generic`` instance should adhere to From git at git.haskell.org Thu Jun 29 17:54:13 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Jun 2017 17:54:13 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: testsuite: Add broken test for #13871 (8dc21c7) Message-ID: <20170629175413.EDB073A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/8dc21c7591bffa1db3ae8c74ce321430900e2d06/ghc >--------------------------------------------------------------- commit 8dc21c7591bffa1db3ae8c74ce321430900e2d06 Author: Ben Gamari Date: Tue Jun 27 10:29:23 2017 -0400 testsuite: Add broken test for #13871 Test Plan: Validate Reviewers: austin Subscribers: rwbarton, thomie, RyanGlScott GHC Trac Issues: #13871 Differential Revision: https://phabricator.haskell.org/D3671 (cherry picked from commit 12a3c394b12e5e07314895e6c419f4f4031ad3a9) >--------------------------------------------------------------- 8dc21c7591bffa1db3ae8c74ce321430900e2d06 testsuite/tests/typecheck/should_compile/T13871.hs | 15 +++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 16 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T13871.hs b/testsuite/tests/typecheck/should_compile/T13871.hs new file mode 100644 index 0000000..319d949 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T13871.hs @@ -0,0 +1,15 @@ +{-# LANGUAGE ConstraintKinds #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeInType #-} +{-# LANGUAGE TypeOperators #-} +module Foo where + +import Data.Kind + +data Foo (a :: Type) (b :: Type) where + MkFoo :: (a ~ Int, b ~ Char) => Foo a b + +data family Sing (a :: k) +data SFoo (z :: Foo a b) where + SMkFoo :: SFoo MkFoo diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 2a6b109..1da16fc 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -554,3 +554,4 @@ 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('T13804', normal, compile, ['']) +test('T13871', expect_broken(13871), compile, ['']) From git at git.haskell.org Thu Jun 29 17:54:16 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Jun 2017 17:54:16 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: typecheck: Consider types containing coercions non-Typeable (40cb68a) Message-ID: <20170629175416.A506A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/40cb68a606ceb082815b2452bfb4eac6ea57522b/ghc >--------------------------------------------------------------- commit 40cb68a606ceb082815b2452bfb4eac6ea57522b Author: Ben Gamari Date: Tue Jun 27 10:29:33 2017 -0400 typecheck: Consider types containing coercions non-Typeable This was previously a panic and caused #13871. I believe just saying these types simply aren't Typeable should be correct. Test Plan: Validate, check `T13871` Reviewers: goldfire, austin Subscribers: rwbarton, thomie, RyanGlScott GHC Trac Issues: #13871 Differential Revision: https://phabricator.haskell.org/D3672 (cherry picked from commit 134652542923e432bffb9fafe87893d785a17aae) >--------------------------------------------------------------- 40cb68a606ceb082815b2452bfb4eac6ea57522b compiler/typecheck/TcTypeable.hs | 2 +- testsuite/tests/typecheck/should_compile/all.T | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index 8d8ea03..76d262c 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -438,7 +438,7 @@ typeIsTypeable (TyConApp tc args) = tyConIsTypeable tc typeIsTypeable (ForAllTy{}) = False typeIsTypeable (LitTy _) = True typeIsTypeable (CastTy{}) = False -typeIsTypeable (CoercionTy{}) = panic "typeIsTypeable(Coercion)" +typeIsTypeable (CoercionTy{}) = False -- | Maps kinds to 'KindRep' bindings. This binding may either be defined in -- some other module (in which case the @Maybe (LHsExpr Id@ will be 'Nothing') diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 1da16fc..f8b86f8 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -554,4 +554,4 @@ 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('T13804', normal, compile, ['']) -test('T13871', expect_broken(13871), compile, ['']) +test('T13871', normal, compile, ['']) From git at git.haskell.org Thu Jun 29 18:01:09 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Jun 2017 18:01:09 +0000 (UTC) Subject: [commit: ghc] master: Typos in comments (c2fb6e8) Message-ID: <20170629180109.9BF063A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c2fb6e8e8e568a9cc7a2da61c4f966c3742c9dbb/ghc >--------------------------------------------------------------- commit c2fb6e8e8e568a9cc7a2da61c4f966c3742c9dbb Author: Ryan Scott Date: Thu Jun 29 14:00:03 2017 -0400 Typos in comments [ci skip] >--------------------------------------------------------------- c2fb6e8e8e568a9cc7a2da61c4f966c3742c9dbb compiler/basicTypes/DataCon.hs | 2 +- compiler/basicTypes/Var.hs | 2 +- compiler/iface/ToIface.hs | 2 +- compiler/types/TyCoRep.hs | 4 ++-- 4 files changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/basicTypes/DataCon.hs b/compiler/basicTypes/DataCon.hs index 1629f36..73bbf2c 100644 --- a/compiler/basicTypes/DataCon.hs +++ b/compiler/basicTypes/DataCon.hs @@ -425,7 +425,7 @@ For the TyVarBinders in a DataCon and PatSyn: Why do we need the TyVarBinders, rather than just the TyVars? So that we can construct the right type for the DataCon with its foralls -attributed the correce visiblity. That in turn governs whether you +attributed the correct visibility. That in turn governs whether you can use visible type application at a call of the data constructor. Note [DataCon arities] diff --git a/compiler/basicTypes/Var.hs b/compiler/basicTypes/Var.hs index d07d9ec..87c4fe2 100644 --- a/compiler/basicTypes/Var.hs +++ b/compiler/basicTypes/Var.hs @@ -404,7 +404,7 @@ sameVis _ _ = True -- Type Variable Binder -- --- TyVarBndr is polymorphic in both tyvar and visiblity fields: +-- TyVarBndr is polymorphic in both tyvar and visibility fields: -- * tyvar can be TyVar or IfaceTv -- * argf can be ArgFlag or TyConBndrVis data TyVarBndr tyvar argf = TvBndr tyvar argf diff --git a/compiler/iface/ToIface.hs b/compiler/iface/ToIface.hs index 59184dc..6f2acba 100644 --- a/compiler/iface/ToIface.hs +++ b/compiler/iface/ToIface.hs @@ -257,7 +257,7 @@ toIfaceTcArgs = toIfaceTcArgsX emptyVarSet toIfaceTcArgsX :: VarSet -> TyCon -> [Type] -> IfaceTcArgs -- See Note [Suppressing invisible arguments] --- We produce a result list of args describing visiblity +-- We produce a result list of args describing visibility -- The awkward case is -- T :: forall k. * -> k -- And consider diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index fbf0a9f..5ac63e5 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -484,7 +484,7 @@ In the kind of a type optional kind applications, thus (T @*), but we have not yet implemented that ----- Examples of where the different visiblities come from ----- +---- Examples of where the different visibilities come from ----- In term declarations: @@ -548,7 +548,7 @@ In type declarations: ---- Printing ----- - We print forall types with enough syntax to tell you their visiblity + We print forall types with enough syntax to tell you their visibility flag. But this is not source Haskell, and these types may not all be parsable. From git at git.haskell.org Thu Jun 29 19:19:49 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Jun 2017 19:19:49 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Treat banged bindings as FunBinds (c7ed911) Message-ID: <20170629191949.D10483A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/c7ed911f1b102f85ba89fe2ccce9ecf8231d1b8c/ghc >--------------------------------------------------------------- commit c7ed911f1b102f85ba89fe2ccce9ecf8231d1b8c Author: Ben Gamari Date: Mon May 8 17:47:19 2017 -0400 Treat banged bindings as FunBinds This is another attempt at resolving #13594 by treating strict variable binds as FunBinds instead of PatBinds (as suggested in comment:1). Test Plan: Validate Reviewers: austin, alanz Subscribers: rwbarton, thomie, mpickering GHC Trac Issues: #13594 Differential Revision: https://phabricator.haskell.org/D3670 (cherry picked from commit 372995364c52eef15066132d7d1ea8b6760034e6) (cherry picked from commit 3032ae81dd14c2eaefa9ecd8880dafa9bda104d9) (cherry picked from commit 6567c815135e93f8550d526f81d13f31c0cd92b6) >--------------------------------------------------------------- c7ed911f1b102f85ba89fe2ccce9ecf8231d1b8c compiler/deSugar/Check.hs | 6 ++-- compiler/deSugar/DsBinds.hs | 33 ++++++++++------- compiler/deSugar/DsExpr.hs | 2 +- compiler/deSugar/DsUtils.hs | 14 +++++++- compiler/deSugar/Match.hs | 9 +++-- compiler/hsSyn/Convert.hs | 6 ++-- compiler/hsSyn/HsBinds.hs | 40 +++++++++++++++++++-- compiler/hsSyn/HsExpr.hs | 42 ++++++++++++++-------- compiler/hsSyn/HsUtils.hs | 19 ++++++++-- compiler/parser/Parser.y | 34 +++++++++++------- compiler/parser/RdrHsSyn.hs | 22 ++++++++---- compiler/rename/RnBinds.hs | 8 ++--- compiler/typecheck/TcGenDeriv.hs | 10 +++--- compiler/typecheck/TcGenFunctor.hs | 5 ++- compiler/typecheck/TcInstDcls.hs | 2 +- compiler/typecheck/TcMatches.hs | 10 ++++-- compiler/typecheck/TcPatSyn.hs | 4 +-- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcTyDecls.hs | 4 +-- testsuite/tests/ghc-api/annotations/T10358.stdout | 6 ++-- .../parser/should_compile/DumpParsedAst.stderr | 3 +- .../parser/should_compile/DumpRenamedAst.stderr | 3 +- .../should_compile/DumpTypecheckedAst.stderr | 3 +- testsuite/tests/typecheck/should_compile/T13594.hs | 8 +++++ testsuite/tests/typecheck/should_compile/all.T | 1 + .../tests/typecheck/should_run/T13594a.script | 2 ++ testsuite/tests/typecheck/should_run/all.T | 1 + 27 files changed, 211 insertions(+), 88 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c7ed911f1b102f85ba89fe2ccce9ecf8231d1b8c From git at git.haskell.org Thu Jun 29 23:31:34 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Jun 2017 23:31:34 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix the in-scope set in TcHsType.instantiateTyN (c1de075) Message-ID: <20170629233134.7F8C63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/c1de0758157097c47de2787c46030174744422b6/ghc >--------------------------------------------------------------- commit c1de0758157097c47de2787c46030174744422b6 Author: Simon Peyton Jones Date: Wed Jun 28 12:32:48 2017 +0100 Fix the in-scope set in TcHsType.instantiateTyN See Trac #13879 (cherry picked from commit 4bdac331207e10650da9d3bf1b446bc8be3c069a) >--------------------------------------------------------------- c1de0758157097c47de2787c46030174744422b6 compiler/typecheck/TcHsType.hs | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 357ffbc..f2369fe 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 ( tcInstBinders, tcInstBindersX, tcInstBinderX ) +import Inst ( tcInstBindersX, tcInstBinderX ) import Type import Kind import RdrName( lookupLocalRdrOcc ) @@ -928,11 +928,16 @@ instantiateTyN n ty ki num_to_inst = length bndrs - n -- NB: splitAt is forgiving with invalid numbers (inst_bndrs, leftover_bndrs) = splitAt num_to_inst bndrs + empty_subst = mkEmptyTCvSubst (mkInScopeSet (tyCoVarsOfType ki)) in if num_to_inst <= 0 then return (ty, ki) else - do { (subst, inst_args) <- tcInstBinders inst_bndrs + do { (subst, inst_args) <- tcInstBindersX 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 subst + , ppr rebuilt_ki + , ppr ki' ]) ; return (mkNakedAppTys ty inst_args, ki') } --------------------------- From git at git.haskell.org Thu Jun 29 23:31:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Jun 2017 23:31:41 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix lexically-scoped type variables (2755f23) Message-ID: <20170629233141.44EE33A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/2755f23919f7429668a933374f2a4ca14a9966b6/ghc >--------------------------------------------------------------- commit 2755f23919f7429668a933374f2a4ca14a9966b6 Author: Simon Peyton Jones Date: Thu Jun 29 15:26:54 2017 +0100 Fix lexically-scoped type variables Trac #13881 showed that our handling of lexically scoped type variables was way off when we bring into scope a name 'y' for a pre-existing type variable 'a', perhaps with an entirely different name. This patch fixes it; see TcHsType Note [Pattern signature binders] (cherry picked from commit 3b0e7555fafe73b157a96ca48d8ddc04ad81b231) >--------------------------------------------------------------- 2755f23919f7429668a933374f2a4ca14a9966b6 compiler/typecheck/TcHsType.hs | 80 +++++++++++++++------- compiler/typecheck/TcPat.hs | 4 +- compiler/typecheck/TcRules.hs | 4 +- testsuite/tests/typecheck/should_compile/T13881.hs | 17 +++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 5 files changed, 78 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 2755f23919f7429668a933374f2a4ca14a9966b6 From git at git.haskell.org Thu Jun 29 23:31:37 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Jun 2017 23:31:37 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Fix constraint solving for forall-types (7d9ca50) Message-ID: <20170629233137.CC9173A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/7d9ca50e184f2bc5da531646673fa7eecfd39862/ghc >--------------------------------------------------------------- commit 7d9ca50e184f2bc5da531646673fa7eecfd39862 Author: Simon Peyton Jones Date: Wed Jun 28 12:38:59 2017 +0100 Fix constraint solving for forall-types Trac #13879 showed that when we were trying to solve (forall z1 (y1::z1). ty1) ~ (forall z2 (y2:z2). ty2) we'd end up spitting out z1~z2 with no binding site for them. Those kind equalities need to be inside the implication. I ended up re-factoring the code for solving forall-equalities. It's quite nice now. (cherry picked from commit fae672f647fe00c303d8fb56971563c1a76ad04e) >--------------------------------------------------------------- 7d9ca50e184f2bc5da531646673fa7eecfd39862 compiler/typecheck/TcCanonical.hs | 95 ++++++++++++++++----- compiler/typecheck/TcSMonad.hs | 98 +++++++++++----------- testsuite/tests/typecheck/should_compile/T13879.hs | 29 +++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + .../tests/typecheck/should_fail/tcfail174.stderr | 2 +- 5 files changed, 152 insertions(+), 73 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7d9ca50e184f2bc5da531646673fa7eecfd39862 From git at git.haskell.org Thu Jun 29 23:31:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Jun 2017 23:31:44 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Do zonking in tcLHsKindSig (3fedc0f) Message-ID: <20170629233144.052143A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/3fedc0fb5820243a1f47c883bb76b829a4a24c85/ghc >--------------------------------------------------------------- commit 3fedc0fb5820243a1f47c883bb76b829a4a24c85 Author: Simon Peyton Jones Date: Wed Jun 28 12:34:41 2017 +0100 Do zonking in tcLHsKindSig Trac #13879 showed that there was a missing zonk in tcLHsKind. I also renamed it to tcLHsKindSig, for consistency with type signatures There's a commment to explain why the zonk is needed. (cherry picked from commit c80920d26f4eef8e87c130412d007628cff7589d) >--------------------------------------------------------------- 3fedc0fb5820243a1f47c883bb76b829a4a24c85 compiler/typecheck/TcHsType.hs | 20 ++++++++++++++------ compiler/typecheck/TcTyClsDecls.hs | 10 +++++----- 2 files changed, 19 insertions(+), 11 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index f2369fe..7992174 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -37,7 +37,7 @@ module TcHsType ( kindGeneralize, -- Sort-checking kinds - tcLHsKind, + tcLHsKindSig, -- Pattern type signatures tcHsPatSigType, tcPatSig, funAppCtxt @@ -1427,7 +1427,7 @@ kcHsTyVarBndrs name unsat cusk open_fam all_kind_vars ; return tv_pair } kc_hs_tv (KindedTyVar (L _ name) lhs_kind) - = do { kind <- tcLHsKind lhs_kind + = do { kind <- tcLHsKindSig lhs_kind ; tcHsTyVarName (Just kind) name } report_non_cusk_tvs all_tvs @@ -1544,7 +1544,7 @@ tcHsTyVarBndr new_tv (UserTyVar (L _ name)) ; new_tv name kind } tcHsTyVarBndr new_tv (KindedTyVar (L _ name) kind) - = do { kind <- tcLHsKind kind + = do { kind <- tcLHsKindSig kind ; new_tv name kind } newWildTyVar :: Name -> TcM TcTyVar @@ -2030,12 +2030,20 @@ unifyKinds act_kinds * * ************************************************************************ -tcLHsKind converts a user-written kind to an internal, sort-checked kind. +tcLHsKindSig converts a user-written kind to an internal, sort-checked kind. It does sort checking and desugaring at the same time, in one single pass. -} -tcLHsKind :: LHsKind Name -> TcM Kind -tcLHsKind = tc_lhs_kind kindLevelMode +tcLHsKindSig :: LHsKind Name -> TcM Kind +tcLHsKindSig hs_kind + = do { kind <- tc_lhs_kind kindLevelMode hs_kind + ; zonkTcType kind } + -- This zonk is very important in the case of higher rank kinds + -- E.g. Trac #13879 f :: forall (p :: forall z (y::z). ). + -- + -- When instanting p's kind at occurrences of p in + -- it's crucial that the kind we instantiate is fully zonked, + -- else we may fail to substitute properly tc_lhs_kind :: TcTyMode -> LHsKind Name -> TcM Kind tc_lhs_kind mode k diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index b510db3..6c5c3aa 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -493,7 +493,7 @@ getInitialKind decl@(DataDecl { tcdLName = L _ name = do { (tycon, _) <- kcHsTyVarBndrs name True (hsDeclHasCusk decl) False True ktvs $ do { res_k <- case m_sig of - Just ksig -> tcLHsKind ksig + Just ksig -> tcLHsKindSig ksig Nothing -> return liftedTypeKind ; return (res_k, ()) } ; return (mkTcTyConEnv tycon) } @@ -508,7 +508,7 @@ getInitialKind decl@(SynDecl { tcdLName = L _ name False {- not open -} True ktvs $ do { res_k <- case kind_annotation rhs of Nothing -> newMetaKindVar - Just ksig -> tcLHsKind ksig + Just ksig -> tcLHsKindSig ksig ; return (res_k, ()) } ; return (mkTcTyConEnv tycon) } where @@ -536,8 +536,8 @@ getFamDeclInitialKind mb_cusk decl@(FamilyDecl { fdLName = L _ name = do { (tycon, _) <- kcHsTyVarBndrs name unsat cusk open True ktvs $ do { res_k <- case resultSig of - KindSig ki -> tcLHsKind ki - TyVarSig (L _ (KindedTyVar _ ki)) -> tcLHsKind ki + KindSig ki -> tcLHsKindSig ki + TyVarSig (L _ (KindedTyVar _ ki)) -> tcLHsKindSig ki _ -- open type families have * return kind by default | open -> return liftedTypeKind -- closed type families have their return kind inferred @@ -1180,7 +1180,7 @@ kcDataDefn fam_name (HsIB { hsib_body = pats }) ; discardResult $ case mb_kind of Nothing -> unifyKind (Just hs_ty_pats) res_k liftedTypeKind - Just k -> do { k' <- tcLHsKind k + Just k -> do { k' <- tcLHsKindSig k ; unifyKind (Just hs_ty_pats) res_k k' } } where hs_ty_pats = mkHsAppTys (noLoc $ HsTyVar NotPromoted (noLoc fam_name)) pats From git at git.haskell.org Fri Jun 30 00:18:27 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Jun 2017 00:18:27 +0000 (UTC) Subject: [commit: ghc] master: Fix T13701 allocation for Linux (c3f12ec) Message-ID: <20170630001827.5A1583A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c3f12ec5edba697cfba199a360c7962bfc9f7e80/ghc >--------------------------------------------------------------- commit c3f12ec5edba697cfba199a360c7962bfc9f7e80 Author: David Feuer Date: Thu Jun 29 19:36:42 2017 -0400 Fix T13701 allocation for Linux For some reason, this test seems to allocate rather more under Linux than under OSX or Windows. Reviewers: austin, bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3684 >--------------------------------------------------------------- c3f12ec5edba697cfba199a360c7962bfc9f7e80 testsuite/tests/perf/compiler/all.T | 1 + 1 file changed, 1 insertion(+) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index f53a84c..10fa715 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -1131,6 +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), (wordsize(64), 2188045288, 10), # initial: 2511285600 # 2017-06-23: 2188045288 treat banged variable bindings as FunBinds From git at git.haskell.org Fri Jun 30 00:18:30 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Jun 2017 00:18:30 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Document FFI safety guarantees (7de2c07) Message-ID: <20170630001830.20A003A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7de2c07d61d8ff952164ee8e6948c1415514ee6d/ghc >--------------------------------------------------------------- commit 7de2c07d61d8ff952164ee8e6948c1415514ee6d Author: Ben Gamari Date: Thu Jun 29 19:36:51 2017 -0400 users-guide: Document FFI safety guarantees Test Plan: Read it Reviewers: austin Subscribers: simonmar, rwbarton, thomie GHC Trac Issues: #13730, #8281 Differential Revision: https://phabricator.haskell.org/D3682 >--------------------------------------------------------------- 7de2c07d61d8ff952164ee8e6948c1415514ee6d docs/users_guide/ffi-chap.rst | 66 +++++++++++++++++++++++++------------------ 1 file changed, 39 insertions(+), 27 deletions(-) diff --git a/docs/users_guide/ffi-chap.rst b/docs/users_guide/ffi-chap.rst index 35557b8..616df29 100644 --- a/docs/users_guide/ffi-chap.rst +++ b/docs/users_guide/ffi-chap.rst @@ -23,6 +23,33 @@ 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 +----------------------------------- + +Guaranteed call safety +~~~~~~~~~~~~~~~~~~~~~~ + +The FFI addendum stipulates that an implementation is free to implement an +``unsafe`` call by performing a ``safe`` call (and therefore may run in 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 +``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 +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 +the bytecode interpreter. This meant that some packages which worked when +compiled would fail under GHCi (e.g. :ghc-ticket:`13730`). + +However, since version 8.4 this is no longer the case: GHC **guarantees** that +garbage collection will never occur during an ``unsafe`` call, even in the +bytecode interpreter. + + .. _ffi-ghcexts: GHC extensions to the FFI Addendum @@ -45,9 +72,7 @@ Newtype wrapping of the IO monad ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The FFI spec requires the IO monad to appear in various places, but it -can sometimes be convenient to wrap the IO monad in a ``newtype``, thus: - -:: +can sometimes be convenient to wrap the IO monad in a ``newtype``, thus: :: newtype MyIO a = MIO (IO a) @@ -59,9 +84,8 @@ imports and exports will be automatically unwrapped if they are newtypes (Section 3.2 of the FFI addendum). GHC extends the FFI by automatically unwrapping any newtypes that wrap the IO monad itself. More precisely, wherever the FFI specification requires an ``IO`` type, GHC will accept any -newtype-wrapping of an ``IO`` type. For example, these declarations are OK: - -:: +newtype-wrapping of an ``IO`` type. For example, these declarations are +OK: :: foreign import foo :: Int -> MyIO Int foreign import "dynamic" baz :: (Int -> MyIO Int) -> CInt -> MyIO Int @@ -72,9 +96,7 @@ Primitive imports ~~~~~~~~~~~~~~~~~ GHC extends the FFI with an additional calling convention ``prim``, -e.g.: - -:: +e.g.: :: foreign import prim "foo" foo :: ByteArray# -> (# Int#, Int# #) @@ -108,9 +130,7 @@ The problem is that it is not possible in general to interrupt a foreign call safely. However, GHC does provide a way to interrupt blocking system calls which works for most system calls on both Unix and Windows. When the ``InterruptibleFFI`` extension is enabled, a foreign call can -be annotated with ``interruptible`` instead of ``safe`` or ``unsafe``: - -:: +be annotated with ``interruptible`` instead of ``safe`` or ``unsafe``: :: foreign import ccall interruptible "sleep" sleepBlock :: CUint -> IO CUint @@ -145,9 +165,7 @@ The CAPI calling convention ~~~~~~~~~~~~~~~~~~~~~~~~~~~ The ``CApiFFI`` extension allows a calling convention of ``capi`` to be -used in foreign declarations, e.g. - -:: +used in foreign declarations, e.g. :: foreign import capi "header.h f" f :: CInt -> IO CInt @@ -157,30 +175,26 @@ ABI, we instead call ``f`` using the C API defined in the header CPP ``#define`` rather than a proper function. When using ``capi``, it is also possible to import values, rather than -functions. For example, - -:: +functions. For example, :: foreign import capi "pi.h value pi" c_pi :: CDouble will work regardless of whether ``pi`` is defined as -:: +.. code-block:: c const double pi = 3.14; or with -:: +.. code-block:: c #define pi 3.14 In order to tell GHC the C type that a Haskell type corresponds to when it is used with the CAPI, a ``CTYPE`` pragma can be used on the type definition. The header which defines the type can optionally also be -specified. The syntax looks like: - -:: +specified. The syntax looks like: :: data {-# CTYPE "unistd.h" "useconds_t" #-} T = ... newtype {-# CTYPE "useconds_t" #-} T = ... @@ -188,7 +202,7 @@ specified. The syntax looks like: ``hs_thread_done()`` ~~~~~~~~~~~~~~~~~~~~ -:: +.. code-block:: c void hs_thread_done(void); @@ -231,9 +245,7 @@ C programs. For a plain ``foreign export``, the file ``M_stub.h`` contains a C prototype for the foreign exported function. For example, if we compile -the following module: - -:: +the following module: :: module Foo where From git at git.haskell.org Fri Jun 30 00:18:32 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Jun 2017 00:18:32 +0000 (UTC) Subject: [commit: ghc] master: configure: Check for binutils #17166 (6171b0b) Message-ID: <20170630001832.D2E523A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6171b0b326e52221a0631cf75eb4866b36abe631/ghc >--------------------------------------------------------------- commit 6171b0b326e52221a0631cf75eb4866b36abe631 Author: Ben Gamari Date: Thu Jun 29 19:37:03 2017 -0400 configure: Check for binutils #17166 This bug affects bfd ld on ARMv7, causing ld to incorrectly emit R_REL_COPY relocations, breaking tables-next-to-code. We've known about it for several years now and there is not yet a fix upstream. Previously we would simply force use of ld.gold on ARM. However, given the rework of linking configuration, I thought a more principled solution was in order. Test Plan: Validate on armv7 Reviewers: austin, hvr Subscribers: angerman, rwbarton, thomie, erikd GHC Trac Issues: #4210 Differential Revision: https://phabricator.haskell.org/D3676 >--------------------------------------------------------------- 6171b0b326e52221a0631cf75eb4866b36abe631 aclocal.m4 | 59 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 59 insertions(+) diff --git a/aclocal.m4 b/aclocal.m4 index db394f3..b94f70b 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2047,6 +2047,65 @@ AC_DEFUN([FIND_LD],[ $2="$LD" ;; esac + CHECK_LD_COPY_BUG($1) +]) + +# CHECK_LD_COPY_BUG() +# ------------------- +# Check for binutils bug #16177 present in some versions of the bfd ld +# implementation affecting ARM relocations. +# https://sourceware.org/bugzilla/show_bug.cgi?id=16177 +# +# $1 = the platform +# +AC_DEFUN([CHECK_LD_COPY_BUG],[ + case $1 in + arm*linux*) + AC_CHECK_TARGET_TOOL([READELF], [readelf]) + AC_CHECK_TARGET_TOOL([AS], [as]) + AC_MSG_CHECKING([for ld bug 16177]) + cat >actest.s <<-EOF + .globl _start + .p2align 4 + _start: + bkpt + + .data + .globl data_object + object_reference: + .long data_object + .size object_reference, 4 +EOF + + cat >aclib.s <<-EOF + .data + .globl data_object + .type data_object, %object + .size data_object, 4 + data_object: + .long 123 +EOF + + $AS -o aclib.o aclib.s + $LD -shared -o aclib.so aclib.o + + $AS -o actest.o actest.s + $LD -o actest actest.o aclib.so + + if $READELF -r actest | grep R_ARM_COPY > /dev/null; then + AC_MSG_RESULT([affected]) + AC_MSG_ERROR( + [Your linker is affected by binutils #16177, which + critically breaks linkage of GHC objects. Please either upgrade + binutils or supply a different linker with the LD environment + variable.]) + else + AC_MSG_RESULT([unaffected]) + fi + ;; + *) + ;; + esac ]) # FIND_GHC_BOOTSTRAP_PROG() From git at git.haskell.org Fri Jun 30 00:18:36 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Jun 2017 00:18:36 +0000 (UTC) Subject: [commit: ghc] master: Allow optional instance keyword in associated type family instances (007f255) Message-ID: <20170630001836.1A7393A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/007f255644f885d445e47e291e50eb12b5ecd08d/ghc >--------------------------------------------------------------- commit 007f255644f885d445e47e291e50eb12b5ecd08d Author: Tibor Erdesz Date: Thu Jun 29 19:37:13 2017 -0400 Allow optional instance keyword in associated type family instances Add the missing branch for parsing the optional 'instance' keyword in associated type family instance declarations. Fixes #13747 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: simonpj, RyanGlScott, rwbarton, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D3673 >--------------------------------------------------------------- 007f255644f885d445e47e291e50eb12b5ecd08d compiler/parser/Parser.y | 34 ++++++++++++++++++++----- docs/users_guide/8.4.1-notes.rst | 3 +++ testsuite/tests/parser/should_compile/T13747.hs | 24 +++++++++++++++++ testsuite/tests/parser/should_compile/all.T | 1 + 4 files changed, 55 insertions(+), 7 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 6e4b774..603ac27 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -1215,25 +1215,37 @@ opt_family :: { [AddAnn] } : {- empty -} { [] } | 'family' { [mj AnnFamily $1] } +opt_instance :: { [AddAnn] } + : {- empty -} { [] } + | 'instance' { [mj AnnInstance $1] } + -- Associated type instances -- at_decl_inst :: { LInstDecl GhcPs } - -- type instance declarations - : 'type' ty_fam_inst_eqn + -- type instance declarations, with optional 'instance' keyword + : 'type' opt_instance ty_fam_inst_eqn -- Note the use of type for the head; this allows -- infix type constructors and type patterns - {% ams $2 (fst $ unLoc $2) >> - amms (mkTyFamInst (comb2 $1 $2) (snd $ unLoc $2)) - (mj AnnType $1:(fst $ unLoc $2)) } + {% ams $3 (fst $ unLoc $3) >> + amms (mkTyFamInst (comb2 $1 $3) (snd $ unLoc $3)) + (mj AnnType $1:$2++(fst $ unLoc $3)) } - -- data/newtype instance declaration + -- data/newtype instance declaration, with optional 'instance' keyword + -- (can't use opt_instance because you get reduce/reduce errors) | data_or_newtype capi_ctype tycl_hdr constrs maybe_derivings {% amms (mkDataFamInst (comb4 $1 $3 $4 $5) (snd $ unLoc $1) $2 $3 Nothing (reverse (snd $ unLoc $4)) (fmap reverse $5)) ((fst $ unLoc $1):(fst $ unLoc $4)) } - -- GADT instance declaration + | data_or_newtype 'instance' capi_ctype tycl_hdr constrs maybe_derivings + {% amms (mkDataFamInst (comb4 $1 $4 $5 $6) (snd $ unLoc $1) $3 $4 + Nothing (reverse (snd $ unLoc $5)) + (fmap reverse $6)) + ((fst $ unLoc $1):mj AnnInstance $2:(fst $ unLoc $5)) } + + -- GADT instance declaration, with optional 'instance' keyword + -- (can't use opt_instance because you get reduce/reduce errors) | data_or_newtype capi_ctype tycl_hdr opt_kind_sig gadt_constrlist maybe_derivings @@ -1242,6 +1254,14 @@ at_decl_inst :: { LInstDecl GhcPs } (fmap reverse $6)) ((fst $ unLoc $1):(fst $ unLoc $4)++(fst $ unLoc $5)) } + | data_or_newtype 'instance' capi_ctype tycl_hdr opt_kind_sig + gadt_constrlist + maybe_derivings + {% amms (mkDataFamInst (comb4 $1 $4 $6 $7) (snd $ unLoc $1) $3 + $4 (snd $ unLoc $5) (snd $ unLoc $6) + (fmap reverse $7)) + ((fst $ unLoc $1):mj AnnInstance $2:(fst $ unLoc $5)++(fst $ unLoc $6)) } + data_or_newtype :: { Located (AddAnn, NewOrData) } : 'data' { sL1 $1 (mj AnnData $1,DataType) } | 'newtype' { sL1 $1 (mj AnnNewtype $1,NewType) } diff --git a/docs/users_guide/8.4.1-notes.rst b/docs/users_guide/8.4.1-notes.rst index f23cb36..7e918f2 100644 --- a/docs/users_guide/8.4.1-notes.rst +++ b/docs/users_guide/8.4.1-notes.rst @@ -80,6 +80,9 @@ Now we generate :: used to build a GHC using compilers on your ``PATH`` instead of using the bundled bindist. See :ghc-ticket:`13792` +- The optional ``instance`` keyword is now usable in type family instance + declarations. See :ghc-ticket:`13747` + - Lots of other bugs. See `Trac `_ for a complete list. diff --git a/testsuite/tests/parser/should_compile/T13747.hs b/testsuite/tests/parser/should_compile/T13747.hs new file mode 100644 index 0000000..749d8d2 --- /dev/null +++ b/testsuite/tests/parser/should_compile/T13747.hs @@ -0,0 +1,24 @@ +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE GADTs #-} + +module T13747 where + +class C a where + type family TC a :: * + +class D a where + data family TD a :: * + +instance C Int where + type instance TC Int = Int + +instance D Double where + data instance TD Double = TDDouble + +instance D Int where + newtype instance TD Int = TDInt Int + +instance D Char where + data instance TD Char where + C1 :: TD Char + C2 :: TD Char diff --git a/testsuite/tests/parser/should_compile/all.T b/testsuite/tests/parser/should_compile/all.T index 2059979..a9d6830 100644 --- a/testsuite/tests/parser/should_compile/all.T +++ b/testsuite/tests/parser/should_compile/all.T @@ -107,3 +107,4 @@ test('T10582', expect_broken(10582), compile, ['']) test('DumpParsedAst', normal, compile, ['-dsuppress-uniques -ddump-parsed-ast']) test('DumpRenamedAst', normal, compile, ['-dsuppress-uniques -ddump-rn-ast']) test('DumpTypecheckedAst', normal, compile, ['-dsuppress-uniques -ddump-tc-ast']) +test('T13747', normal, compile, ['']) From git at git.haskell.org Fri Jun 30 00:18:41 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Jun 2017 00:18:41 +0000 (UTC) Subject: [commit: ghc] master: rts/RetainerProfile: Const-correctness fixes (9b514de) Message-ID: <20170630001841.ACD913A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9b514dedf090c5e21e3be38d174cf1390e21879f/ghc >--------------------------------------------------------------- commit 9b514dedf090c5e21e3be38d174cf1390e21879f Author: Ben Gamari Date: Thu Jun 29 19:39:28 2017 -0400 rts/RetainerProfile: Const-correctness fixes These were found while using Hadrian, which apparently uses slightly stricter warning flags than the make-based build system. Test Plan: Validate Reviewers: austin, erikd, simonmar Reviewed By: erikd Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3679 >--------------------------------------------------------------- 9b514dedf090c5e21e3be38d174cf1390e21879f rts/RetainerProfile.c | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/rts/RetainerProfile.c b/rts/RetainerProfile.c index 54a1067..6ca09fc 100644 --- a/rts/RetainerProfile.c +++ b/rts/RetainerProfile.c @@ -322,7 +322,7 @@ find_ptrs( stackPos *info ) * Initializes *info from SRT information stored in *infoTable. * -------------------------------------------------------------------------- */ static INLINE void -init_srt_fun( stackPos *info, StgFunInfoTable *infoTable ) +init_srt_fun( stackPos *info, const StgFunInfoTable *infoTable ) { if (infoTable->i.srt_bitmap == (StgHalfWord)(-1)) { info->type = posTypeLargeSRT; @@ -336,7 +336,7 @@ init_srt_fun( stackPos *info, StgFunInfoTable *infoTable ) } static INLINE void -init_srt_thunk( stackPos *info, StgThunkInfoTable *infoTable ) +init_srt_thunk( stackPos *info, const StgThunkInfoTable *infoTable ) { if (infoTable->i.srt_bitmap == (StgHalfWord)(-1)) { info->type = posTypeLargeSRT; @@ -1279,7 +1279,7 @@ retainStack( StgClosure *c, retainer c_child_r, { stackElement *oldStackBoundary; StgPtr p; - StgRetInfoTable *info; + const StgRetInfoTable *info; StgWord bitmap; uint32_t size; @@ -1355,7 +1355,7 @@ retainStack( StgClosure *c, retainer c_child_r, case RET_FUN: { StgRetFun *ret_fun = (StgRetFun *)p; - StgFunInfoTable *fun_info; + const StgFunInfoTable *fun_info; retainClosure(ret_fun->fun, c, c_child_r); fun_info = get_fun_itbl(UNTAG_CONST_CLOSURE(ret_fun->fun)); @@ -1411,7 +1411,7 @@ retain_PAP_payload (StgClosure *pap, /* NOT tagged */ { StgPtr p; StgWord bitmap; - StgFunInfoTable *fun_info; + const StgFunInfoTable *fun_info; retainClosure(fun, pap, c_child_r); fun = UNTAG_CLOSURE(fun); @@ -1669,10 +1669,10 @@ inner_loop: { StgTSO *tso = (StgTSO *)c; - retainClosure(tso->stackobj, c, c_child_r); - retainClosure(tso->blocked_exceptions, c, c_child_r); - retainClosure(tso->bq, c, c_child_r); - retainClosure(tso->trec, c, c_child_r); + retainClosure((StgClosure*) tso->stackobj, c, c_child_r); + retainClosure((StgClosure*) tso->blocked_exceptions, c, c_child_r); + retainClosure((StgClosure*) tso->bq, c, c_child_r); + retainClosure((StgClosure*) tso->trec, c, c_child_r); if ( tso->why_blocked == BlockedOnMVar || tso->why_blocked == BlockedOnMVarRead || tso->why_blocked == BlockedOnBlackHole From git at git.haskell.org Fri Jun 30 00:18:38 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Jun 2017 00:18:38 +0000 (UTC) Subject: [commit: ghc] master: configure: Coerce gcc to use $LD instead of system default (625143f) Message-ID: <20170630001838.E013A3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/625143f473b58d770d2515b91c2566b52d35a4c3/ghc >--------------------------------------------------------------- commit 625143f473b58d770d2515b91c2566b52d35a4c3 Author: Ben Gamari Date: Thu Jun 29 19:38:51 2017 -0400 configure: Coerce gcc to use $LD instead of system default The configure script will now try to coerce gcc to use the linker pointed to by $LD instead of the system default (typically bfd ld). Moreover, we now check for `ld.gold` and `ld.lld` before trying `ld`. The previous behavior can be reverted to by using the new --disable-ld-override flag. On my machine gold seems to trigger an apparent infelicity in constructor behavior, causing T5435_asm to fail. I've opened #13883 to record this issue and have accepted the questionable constructor ordering for the time being. Test Plan: Validate with `config_args='--enable-ld-override'` Reviewers: austin, hvr, simonmar Subscribers: duog, nh2, rwbarton, thomie, erikd, snowleopard GHC Trac Issues: #13541, #13810, #13883 Differential Revision: https://phabricator.haskell.org/D3449 >--------------------------------------------------------------- 625143f473b58d770d2515b91c2566b52d35a4c3 aclocal.m4 | 106 ++++++++++++++++++++++++++-------------------- configure.ac | 9 ++-- distrib/configure.ac.in | 25 +++++------ testsuite/tests/rts/all.T | 4 ++ 4 files changed, 82 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 625143f473b58d770d2515b91c2566b52d35a4c3 From git at git.haskell.org Fri Jun 30 00:18:44 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Jun 2017 00:18:44 +0000 (UTC) Subject: [commit: ghc] master: Prevent ApplicativeDo from applying to strict pattern matches (#13875) (1ef4156) Message-ID: <20170630001844.E14303A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1ef4156e45dcb258f6ef05cfb909547b8e3beb0f/ghc >--------------------------------------------------------------- commit 1ef4156e45dcb258f6ef05cfb909547b8e3beb0f Author: Simon Marlow Date: Thu Jun 29 19:39:45 2017 -0400 Prevent ApplicativeDo from applying to strict pattern matches (#13875) Test Plan: * New unit tests * validate Reviewers: dfeuer, simonpj, niteria, bgamari, austin, erikd Reviewed By: dfeuer Subscribers: rwbarton, thomie GHC Trac Issues: #13875 Differential Revision: https://phabricator.haskell.org/D3681 >--------------------------------------------------------------- 1ef4156e45dcb258f6ef05cfb909547b8e3beb0f compiler/rename/RnExpr.hs | 62 +++++++++++++++++++++++++++++++++++---- testsuite/tests/ado/T13875.hs | 36 +++++++++++++++++++++++ testsuite/tests/ado/ado001.hs | 10 +++++++ testsuite/tests/ado/ado001.stdout | 1 + testsuite/tests/ado/all.T | 1 + 5 files changed, 104 insertions(+), 6 deletions(-) diff --git a/compiler/rename/RnExpr.hs b/compiler/rename/RnExpr.hs index 2c779d2..c5c75ab 100644 --- a/compiler/rename/RnExpr.hs +++ b/compiler/rename/RnExpr.hs @@ -1635,12 +1635,8 @@ stmtTreeToStmts -- the bind form, which would give rise to a Monad constraint. stmtTreeToStmts monad_names ctxt (StmtTreeOne (L _ (BindStmt pat rhs _ _ _),_)) tail _tail_fvs - | isIrrefutableHsPat pat, (False,tail') <- needJoin monad_names tail - -- WARNING: isIrrefutableHsPat on (HsPat Name) doesn't have enough info - -- to know which types have only one constructor. So only - -- tuples come out as irrefutable; other single-constructor - -- types, and newtypes, will not. See the code for - -- isIrrefuatableHsPat + | not (isStrictPattern pat), (False,tail') <- needJoin monad_names tail + -- See Note [ApplicativeDo and strict patterns] = mkApplicativeStmt ctxt [ApplicativeArgOne pat rhs] False tail' stmtTreeToStmts _monad_names _ctxt (StmtTreeOne (s,_)) tail _tail_fvs = @@ -1715,6 +1711,8 @@ segments stmts = map fst $ merge $ reverse $ map reverse $ walk (reverse stmts) chunter _ [] = ([], []) chunter vars ((stmt,fvs) : rest) | not (isEmptyNameSet vars) + || isStrictPatternBind stmt + -- See Note [ApplicativeDo and strict patterns] = ((stmt,fvs) : chunk, rest') where (chunk,rest') = chunter vars' rest (pvars, evars) = stmtRefs stmt fvs @@ -1727,6 +1725,58 @@ segments stmts = map fst $ merge $ reverse $ map reverse $ walk (reverse stmts) where fvs' = fvs `intersectNameSet` allvars pvars = mkNameSet (collectStmtBinders (unLoc stmt)) + isStrictPatternBind :: ExprLStmt GhcRn -> Bool + isStrictPatternBind (L _ (BindStmt pat _ _ _ _)) = isStrictPattern pat + isStrictPatternBind _ = False + +{- +Note [ApplicativeDo and strict patterns] + +A strict pattern match is really a dependency. For example, + +do + (x,y) <- A + z <- B + return C + +The pattern (_,_) must be matched strictly before we do B. If we +allowed this to be transformed into + + (\(x,y) -> \z -> C) <$> A <*> B + +then it could be lazier than the standard desuraging using >>=. See #13875 +for more examples. + +Thus, whenever we have a strict pattern match, we treat it as a +dependency between that statement and the following one. The +dependency prevents those two statements from being performed "in +parallel" in an ApplicativeStmt, but doesn't otherwise affect what we +can do with the rest of the statements in the same "do" expression. +-} + +isStrictPattern :: LPat id -> Bool +isStrictPattern (L _ pat) = + case pat of + WildPat{} -> False + VarPat{} -> False + LazyPat{} -> False + AsPat _ p -> isStrictPattern p + ParPat p -> isStrictPattern p + ViewPat _ p _ -> isStrictPattern p + SigPatIn p _ -> isStrictPattern p + SigPatOut p _ -> isStrictPattern p + BangPat{} -> True + TuplePat{} -> True + SumPat{} -> True + PArrPat{} -> True + ConPatIn{} -> True + ConPatOut{} -> True + LitPat{} -> True + NPat{} -> True + NPlusKPat{} -> True + SplicePat{} -> True + _otherwise -> panic "isStrictPattern" + isLetStmt :: LStmt a b -> Bool isLetStmt (L _ LetStmt{}) = True isLetStmt _ = False diff --git a/testsuite/tests/ado/T13875.hs b/testsuite/tests/ado/T13875.hs new file mode 100644 index 0000000..df35331 --- /dev/null +++ b/testsuite/tests/ado/T13875.hs @@ -0,0 +1,36 @@ +{-# LANGUAGE ApplicativeDo #-} +module Main where + +import Control.Exception +import Control.Monad +import Data.Maybe +import System.Exit + +test0 :: Maybe () +test0 = do + () <- Just undefined + () <- Just undefined + return () + +test1 :: Maybe () +test1 = do + (_,_) <- Just undefined + return () + +test2 :: Maybe (Int,Int) +test2 = do + x <- return 1 + () <- Just undefined + y <- return 2 + return (x,y) + +main = do + b <- (print (isJust test0) >> return True) + `catch` \ErrorCall{} -> return False + when b $ die "failed0" + b <- (print (isJust test1) >> return True) + `catch` \ErrorCall{} -> return False + when b $ die "failed1" + b <- (print (isJust test2) >> return True) + `catch` \ErrorCall{} -> return False + when b $ die "failed2" diff --git a/testsuite/tests/ado/ado001.hs b/testsuite/tests/ado/ado001.hs index e452cdd..0d466c5 100644 --- a/testsuite/tests/ado/ado001.hs +++ b/testsuite/tests/ado/ado001.hs @@ -120,6 +120,15 @@ test11 = do x5 = x4 return (const () (x1,x2,x3,x4)) +-- (a | (b ; c)) +-- The strict pattern match forces (b;c), but a can still be parallel (#13875) +test12 :: M () +test12 = do + x1 <- a + () <- b + x2 <- c + return (const () (x1,x2)) + main = mapM_ run [ test1 , test2 @@ -132,6 +141,7 @@ main = mapM_ run , test9 , test10 , test11 + , test12 ] -- Testing code, prints out the structure of a monad/applicative expression diff --git a/testsuite/tests/ado/ado001.stdout b/testsuite/tests/ado/ado001.stdout index f7c48ca..365860f 100644 --- a/testsuite/tests/ado/ado001.stdout +++ b/testsuite/tests/ado/ado001.stdout @@ -9,3 +9,4 @@ a; ((b | c) | d) ((a | (b; c)) | d) | e ((a | b); (c | d)) | e a | b +a | (b; c) diff --git a/testsuite/tests/ado/all.T b/testsuite/tests/ado/all.T index 6a1b4ec..a738c7a 100644 --- a/testsuite/tests/ado/all.T +++ b/testsuite/tests/ado/all.T @@ -9,3 +9,4 @@ test('T11607', normal, compile_and_run, ['']) test('ado-optimal', normal, compile_and_run, ['']) test('T12490', normal, compile, ['']) test('T13242', normal, compile, ['']) +test('T13875', normal, compile_and_run, ['']) From git at git.haskell.org Fri Jun 30 02:26:21 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Jun 2017 02:26:21 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: configure: Check for binutils #17166 (21cd772) Message-ID: <20170630022621.042B63A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/21cd77200d52e2baa15e318efc7495d4fd34b7c0/ghc >--------------------------------------------------------------- commit 21cd77200d52e2baa15e318efc7495d4fd34b7c0 Author: Ben Gamari Date: Thu Jun 29 19:37:03 2017 -0400 configure: Check for binutils #17166 This bug affects bfd ld on ARMv7, causing ld to incorrectly emit R_REL_COPY relocations, breaking tables-next-to-code. We've known about it for several years now and there is not yet a fix upstream. Previously we would simply force use of ld.gold on ARM. However, given the rework of linking configuration, I thought a more principled solution was in order. Test Plan: Validate on armv7 Reviewers: austin, hvr Subscribers: angerman, rwbarton, thomie, erikd GHC Trac Issues: #4210 Differential Revision: https://phabricator.haskell.org/D3676 (cherry picked from commit 6171b0b326e52221a0631cf75eb4866b36abe631) >--------------------------------------------------------------- 21cd77200d52e2baa15e318efc7495d4fd34b7c0 aclocal.m4 | 59 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 59 insertions(+) diff --git a/aclocal.m4 b/aclocal.m4 index 2b12c0f..88af689 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2090,6 +2090,65 @@ AC_DEFUN([FIND_LD],[ $1="$LD" ;; esac + CHECK_LD_COPY_BUG($1) +]) + +# CHECK_LD_COPY_BUG() +# ------------------- +# Check for binutils bug #16177 present in some versions of the bfd ld +# implementation affecting ARM relocations. +# https://sourceware.org/bugzilla/show_bug.cgi?id=16177 +# +# $1 = the platform +# +AC_DEFUN([CHECK_LD_COPY_BUG],[ + case $1 in + arm*linux*) + AC_CHECK_TARGET_TOOL([READELF], [readelf]) + AC_CHECK_TARGET_TOOL([AS], [as]) + AC_MSG_CHECKING([for ld bug 16177]) + cat >actest.s <<-EOF + .globl _start + .p2align 4 + _start: + bkpt + + .data + .globl data_object + object_reference: + .long data_object + .size object_reference, 4 +EOF + + cat >aclib.s <<-EOF + .data + .globl data_object + .type data_object, %object + .size data_object, 4 + data_object: + .long 123 +EOF + + $AS -o aclib.o aclib.s + $LD -shared -o aclib.so aclib.o + + $AS -o actest.o actest.s + $LD -o actest actest.o aclib.so + + if $READELF -r actest | grep R_ARM_COPY > /dev/null; then + AC_MSG_RESULT([affected]) + AC_MSG_ERROR( + [Your linker is affected by binutils #16177, which + critically breaks linkage of GHC objects. Please either upgrade + binutils or supply a different linker with the LD environment + variable.]) + else + AC_MSG_RESULT([unaffected]) + fi + ;; + *) + ;; + esac ]) # FIND_GHC_BOOTSTRAP_PROG() From git at git.haskell.org Fri Jun 30 02:26:26 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Jun 2017 02:26:26 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: rts/RetainerProfile: Const-correctness fixes (94af73b) Message-ID: <20170630022626.6F4CD3A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/94af73ba7d0746ece4ecafca04e4b0a0cf767d31/ghc >--------------------------------------------------------------- commit 94af73ba7d0746ece4ecafca04e4b0a0cf767d31 Author: Ben Gamari Date: Thu Jun 29 19:39:28 2017 -0400 rts/RetainerProfile: Const-correctness fixes These were found while using Hadrian, which apparently uses slightly stricter warning flags than the make-based build system. Test Plan: Validate Reviewers: austin, erikd, simonmar Reviewed By: erikd Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3679 (cherry picked from commit 9b514dedf090c5e21e3be38d174cf1390e21879f) >--------------------------------------------------------------- 94af73ba7d0746ece4ecafca04e4b0a0cf767d31 rts/RetainerProfile.c | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/rts/RetainerProfile.c b/rts/RetainerProfile.c index 9012937..7253233 100644 --- a/rts/RetainerProfile.c +++ b/rts/RetainerProfile.c @@ -322,7 +322,7 @@ find_ptrs( stackPos *info ) * Initializes *info from SRT information stored in *infoTable. * -------------------------------------------------------------------------- */ static INLINE void -init_srt_fun( stackPos *info, StgFunInfoTable *infoTable ) +init_srt_fun( stackPos *info, const StgFunInfoTable *infoTable ) { if (infoTable->i.srt_bitmap == (StgHalfWord)(-1)) { info->type = posTypeLargeSRT; @@ -336,7 +336,7 @@ init_srt_fun( stackPos *info, StgFunInfoTable *infoTable ) } static INLINE void -init_srt_thunk( stackPos *info, StgThunkInfoTable *infoTable ) +init_srt_thunk( stackPos *info, const StgThunkInfoTable *infoTable ) { if (infoTable->i.srt_bitmap == (StgHalfWord)(-1)) { info->type = posTypeLargeSRT; @@ -1279,7 +1279,7 @@ retainStack( StgClosure *c, retainer c_child_r, { stackElement *oldStackBoundary; StgPtr p; - StgRetInfoTable *info; + const StgRetInfoTable *info; StgWord bitmap; uint32_t size; @@ -1355,7 +1355,7 @@ retainStack( StgClosure *c, retainer c_child_r, case RET_FUN: { StgRetFun *ret_fun = (StgRetFun *)p; - StgFunInfoTable *fun_info; + const StgFunInfoTable *fun_info; retainClosure(ret_fun->fun, c, c_child_r); fun_info = get_fun_itbl(UNTAG_CONST_CLOSURE(ret_fun->fun)); @@ -1411,7 +1411,7 @@ retain_PAP_payload (StgClosure *pap, /* NOT tagged */ { StgPtr p; StgWord bitmap; - StgFunInfoTable *fun_info; + const StgFunInfoTable *fun_info; retainClosure(fun, pap, c_child_r); fun = UNTAG_CLOSURE(fun); @@ -1669,10 +1669,10 @@ inner_loop: { StgTSO *tso = (StgTSO *)c; - retainClosure(tso->stackobj, c, c_child_r); - retainClosure(tso->blocked_exceptions, c, c_child_r); - retainClosure(tso->bq, c, c_child_r); - retainClosure(tso->trec, c, c_child_r); + retainClosure((StgClosure*) tso->stackobj, c, c_child_r); + retainClosure((StgClosure*) tso->blocked_exceptions, c, c_child_r); + retainClosure((StgClosure*) tso->bq, c, c_child_r); + retainClosure((StgClosure*) tso->trec, c, c_child_r); if ( tso->why_blocked == BlockedOnMVar || tso->why_blocked == BlockedOnMVarRead || tso->why_blocked == BlockedOnBlackHole From git at git.haskell.org Fri Jun 30 02:26:29 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Jun 2017 02:26:29 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Prevent ApplicativeDo from applying to strict pattern matches (#13875) (97aa533) Message-ID: <20170630022629.914763A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/97aa533fd8bcbd8e42b3358e8a07423ad2a2d01f/ghc >--------------------------------------------------------------- commit 97aa533fd8bcbd8e42b3358e8a07423ad2a2d01f Author: Simon Marlow Date: Thu Jun 29 19:39:45 2017 -0400 Prevent ApplicativeDo from applying to strict pattern matches (#13875) Test Plan: * New unit tests * validate Reviewers: dfeuer, simonpj, niteria, bgamari, austin, erikd Reviewed By: dfeuer Subscribers: rwbarton, thomie GHC Trac Issues: #13875 Differential Revision: https://phabricator.haskell.org/D3681 (cherry picked from commit 1ef4156e45dcb258f6ef05cfb909547b8e3beb0f) >--------------------------------------------------------------- 97aa533fd8bcbd8e42b3358e8a07423ad2a2d01f compiler/rename/RnExpr.hs | 62 +++++++++++++++++++++++++++++++++++---- testsuite/tests/ado/T13875.hs | 36 +++++++++++++++++++++++ testsuite/tests/ado/ado001.hs | 10 +++++++ testsuite/tests/ado/ado001.stdout | 1 + testsuite/tests/ado/all.T | 1 + 5 files changed, 104 insertions(+), 6 deletions(-) diff --git a/compiler/rename/RnExpr.hs b/compiler/rename/RnExpr.hs index fe3d308..001bc46 100644 --- a/compiler/rename/RnExpr.hs +++ b/compiler/rename/RnExpr.hs @@ -1622,12 +1622,8 @@ stmtTreeToStmts -- the bind form, which would give rise to a Monad constraint. stmtTreeToStmts monad_names ctxt (StmtTreeOne (L _ (BindStmt pat rhs _ _ _),_)) tail _tail_fvs - | isIrrefutableHsPat pat, (False,tail') <- needJoin monad_names tail - -- WARNING: isIrrefutableHsPat on (HsPat Name) doesn't have enough info - -- to know which types have only one constructor. So only - -- tuples come out as irrefutable; other single-constructor - -- types, and newtypes, will not. See the code for - -- isIrrefuatableHsPat + | not (isStrictPattern pat), (False,tail') <- needJoin monad_names tail + -- See Note [ApplicativeDo and strict patterns] = mkApplicativeStmt ctxt [ApplicativeArgOne pat rhs] False tail' stmtTreeToStmts _monad_names _ctxt (StmtTreeOne (s,_)) tail _tail_fvs = @@ -1702,6 +1698,8 @@ segments stmts = map fst $ merge $ reverse $ map reverse $ walk (reverse stmts) chunter _ [] = ([], []) chunter vars ((stmt,fvs) : rest) | not (isEmptyNameSet vars) + || isStrictPatternBind stmt + -- See Note [ApplicativeDo and strict patterns] = ((stmt,fvs) : chunk, rest') where (chunk,rest') = chunter vars' rest (pvars, evars) = stmtRefs stmt fvs @@ -1714,6 +1712,58 @@ segments stmts = map fst $ merge $ reverse $ map reverse $ walk (reverse stmts) where fvs' = fvs `intersectNameSet` allvars pvars = mkNameSet (collectStmtBinders (unLoc stmt)) + isStrictPatternBind :: ExprLStmt Name -> Bool + isStrictPatternBind (L _ (BindStmt pat _ _ _ _)) = isStrictPattern pat + isStrictPatternBind _ = False + +{- +Note [ApplicativeDo and strict patterns] + +A strict pattern match is really a dependency. For example, + +do + (x,y) <- A + z <- B + return C + +The pattern (_,_) must be matched strictly before we do B. If we +allowed this to be transformed into + + (\(x,y) -> \z -> C) <$> A <*> B + +then it could be lazier than the standard desuraging using >>=. See #13875 +for more examples. + +Thus, whenever we have a strict pattern match, we treat it as a +dependency between that statement and the following one. The +dependency prevents those two statements from being performed "in +parallel" in an ApplicativeStmt, but doesn't otherwise affect what we +can do with the rest of the statements in the same "do" expression. +-} + +isStrictPattern :: LPat id -> Bool +isStrictPattern (L _ pat) = + case pat of + WildPat{} -> False + VarPat{} -> False + LazyPat{} -> False + AsPat _ p -> isStrictPattern p + ParPat p -> isStrictPattern p + ViewPat _ p _ -> isStrictPattern p + SigPatIn p _ -> isStrictPattern p + SigPatOut p _ -> isStrictPattern p + BangPat{} -> True + TuplePat{} -> True + SumPat{} -> True + PArrPat{} -> True + ConPatIn{} -> True + ConPatOut{} -> True + LitPat{} -> True + NPat{} -> True + NPlusKPat{} -> True + SplicePat{} -> True + _otherwise -> panic "isStrictPattern" + isLetStmt :: LStmt a b -> Bool isLetStmt (L _ LetStmt{}) = True isLetStmt _ = False diff --git a/testsuite/tests/ado/T13875.hs b/testsuite/tests/ado/T13875.hs new file mode 100644 index 0000000..df35331 --- /dev/null +++ b/testsuite/tests/ado/T13875.hs @@ -0,0 +1,36 @@ +{-# LANGUAGE ApplicativeDo #-} +module Main where + +import Control.Exception +import Control.Monad +import Data.Maybe +import System.Exit + +test0 :: Maybe () +test0 = do + () <- Just undefined + () <- Just undefined + return () + +test1 :: Maybe () +test1 = do + (_,_) <- Just undefined + return () + +test2 :: Maybe (Int,Int) +test2 = do + x <- return 1 + () <- Just undefined + y <- return 2 + return (x,y) + +main = do + b <- (print (isJust test0) >> return True) + `catch` \ErrorCall{} -> return False + when b $ die "failed0" + b <- (print (isJust test1) >> return True) + `catch` \ErrorCall{} -> return False + when b $ die "failed1" + b <- (print (isJust test2) >> return True) + `catch` \ErrorCall{} -> return False + when b $ die "failed2" diff --git a/testsuite/tests/ado/ado001.hs b/testsuite/tests/ado/ado001.hs index e452cdd..0d466c5 100644 --- a/testsuite/tests/ado/ado001.hs +++ b/testsuite/tests/ado/ado001.hs @@ -120,6 +120,15 @@ test11 = do x5 = x4 return (const () (x1,x2,x3,x4)) +-- (a | (b ; c)) +-- The strict pattern match forces (b;c), but a can still be parallel (#13875) +test12 :: M () +test12 = do + x1 <- a + () <- b + x2 <- c + return (const () (x1,x2)) + main = mapM_ run [ test1 , test2 @@ -132,6 +141,7 @@ main = mapM_ run , test9 , test10 , test11 + , test12 ] -- Testing code, prints out the structure of a monad/applicative expression diff --git a/testsuite/tests/ado/ado001.stdout b/testsuite/tests/ado/ado001.stdout index f7c48ca..365860f 100644 --- a/testsuite/tests/ado/ado001.stdout +++ b/testsuite/tests/ado/ado001.stdout @@ -9,3 +9,4 @@ a; ((b | c) | d) ((a | (b; c)) | d) | e ((a | b); (c | d)) | e a | b +a | (b; c) diff --git a/testsuite/tests/ado/all.T b/testsuite/tests/ado/all.T index 6a1b4ec..a738c7a 100644 --- a/testsuite/tests/ado/all.T +++ b/testsuite/tests/ado/all.T @@ -9,3 +9,4 @@ test('T11607', normal, compile_and_run, ['']) test('ado-optimal', normal, compile_and_run, ['']) test('T12490', normal, compile, ['']) test('T13242', normal, compile, ['']) +test('T13875', normal, compile_and_run, ['']) From git at git.haskell.org Fri Jun 30 02:26:23 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Jun 2017 02:26:23 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: configure: Coerce gcc to use $LD instead of system default (2785ef0) Message-ID: <20170630022623.BAD183A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/2785ef0e31a123400da950ffafebe6cb1ce3f4eb/ghc >--------------------------------------------------------------- commit 2785ef0e31a123400da950ffafebe6cb1ce3f4eb Author: Ben Gamari Date: Thu Jun 29 19:38:51 2017 -0400 configure: Coerce gcc to use $LD instead of system default The configure script will now try to coerce gcc to use the linker pointed to by $LD instead of the system default (typically bfd ld). Moreover, we now check for `ld.gold` and `ld.lld` before trying `ld`. The previous behavior can be reverted to by using the new --disable-ld-override flag. On my machine gold seems to trigger an apparent infelicity in constructor behavior, causing T5435_asm to fail. I've opened #13883 to record this issue and have accepted the questionable constructor ordering for the time being. Test Plan: Validate with `config_args='--enable-ld-override'` Reviewers: austin, hvr, simonmar Subscribers: duog, nh2, rwbarton, thomie, erikd, snowleopard GHC Trac Issues: #13541, #13810, #13883 Differential Revision: https://phabricator.haskell.org/D3449 (cherry picked from commit 625143f473b58d770d2515b91c2566b52d35a4c3) >--------------------------------------------------------------- 2785ef0e31a123400da950ffafebe6cb1ce3f4eb aclocal.m4 | 91 +++++++++++++++++++++++++++++++---------------- configure.ac | 7 ++-- distrib/configure.ac.in | 25 ++++++------- testsuite/tests/rts/all.T | 4 +++ 4 files changed, 83 insertions(+), 44 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 88af689..4ecd1bb 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -623,15 +623,12 @@ AC_DEFUN([FPTOOLS_SET_C_LD_FLAGS], # instructions (ie not Thumb) and to link using the gold linker. # Forcing LD to be ld.gold is done in FIND_LD m4 macro. $2="$$2 -marm" - $3="$$3 -fuse-ld=gold -Wl,-z,noexecstack" + $3="$$3 -Wl,-z,noexecstack" $4="$$4 -z noexecstack" ;; aarch64*linux*) - # On aarch64/linux and aarch64/android, tell gcc to link using the - # gold linker. - # Forcing LD to be ld.gold is done in FIND_LD m4 macro. - $3="$$3 -fuse-ld=gold -Wl,-z,noexecstack" + $3="$$3 -Wl,-z,noexecstack" $4="$$4 -z noexecstack" ;; @@ -2068,31 +2065,6 @@ AC_DEFUN([FIND_LLVM_PROG],[ fi ]) -# FIND_LD -# Find the version of `ld` to use. This is used in both in the top level -# configure.ac and in distrib/configure.ac.in. -# -# $1 = the variable to set -# -AC_DEFUN([FIND_LD],[ - FP_ARG_WITH_PATH_GNU_PROG([LD], [ld], [ld]) - case $target in - arm*linux* | \ - aarch64*linux* ) - # Arm and Aarch64 requires use of the binutils ld.gold linker. - # This case should catch at least arm-unknown-linux-gnueabihf, - # arm-linux-androideabi, arm64-unknown-linux and - # aarch64-linux-android - FP_ARG_WITH_PATH_GNU_PROG([LD_GOLD], [ld.gold], [ld.gold]) - $1="$LD_GOLD" - ;; - *) - $1="$LD" - ;; - esac - CHECK_LD_COPY_BUG($1) -]) - # CHECK_LD_COPY_BUG() # ------------------- # Check for binutils bug #16177 present in some versions of the bfd ld @@ -2327,4 +2299,63 @@ AC_DEFUN([FP_BFD_SUPPORT], [ ) ]) + +# FP_CC_LINKER_FLAG_TRY() +# -------------------- +# Try a particular linker to see whether we can use it. In particular, determine +# whether we can convince gcc to use it via a -fuse-ld=... flag. +# +# $1 = the name of the linker to try +# $2 = the variable to set with the appropriate GHC flag if the linker is +# found to be usable +AC_DEFUN([FP_CC_LINKER_FLAG_TRY], [ + AC_MSG_CHECKING([whether C compiler supports -fuse-ld=$1]) + echo 'int main(void) {return 0;}' > conftest.c + if $CC -o conftest.o -fuse-ld=$1 conftest.c > /dev/null 2>&1 + then + $2="-fuse-ld=$1" + AC_MSG_RESULT([yes]) + else + AC_MSG_RESULT([no]) + fi + rm -f conftest.c conftest.o +]) + +# FIND_LD +# --------- +# Find the version of `ld` to use and figure out how to get gcc to use it for +# linking (if --enable-ld-override is enabled). This is used in both in the top +# level configure.ac and in distrib/configure.ac.in. +# +# $1 = the platform +# $2 = the variable to set with GHC options to configure gcc to use the chosen linker +# +AC_DEFUN([FIND_LD],[ + AC_ARG_ENABLE(ld-override, + [AC_HELP_STRING([--disable-ld-override], + [Prevent GHC from overriding the default linker used by gcc. If ld-override is enabled GHC will try to tell gcc to use whichever linker is selected by the LD environment variable. [default=override enabled]])], + [], + [enable_ld_override=yes]) + + if test "x$enable_ld_override" = "xyes"; then + AC_CHECK_TARGET_TOOLS([LD], [ld.gold ld.lld ld]) + UseLd='' + + out=`$LD --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']) + fi + else + AC_CHECK_TARGET_TOOL([LD], [ld]) + fi + + CHECK_LD_COPY_BUG([$1]) +]) + # LocalWords: fi diff --git a/configure.ac b/configure.ac index 9a47524..27d879d 100644 --- a/configure.ac +++ b/configure.ac @@ -495,9 +495,12 @@ FP_SET_CFLAGS_C99([CC_STAGE0],[CONF_CC_OPTS_STAGE0],[CONF_CPP_OPTS_STAGE0]) FP_SET_CFLAGS_C99([CC],[CONF_CC_OPTS_STAGE1],[CONF_CPP_OPTS_STAGE1]) FP_SET_CFLAGS_C99([CC],[CONF_CC_OPTS_STAGE2],[CONF_CPP_OPTS_STAGE2]) -dnl ** Which ld to use? +dnl ** Choose a linker dnl -------------------------------------------------------------- -FIND_LD([LdCmd]) +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" AC_SUBST([LdCmd]) dnl ** Which nm to use? diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index e733f64..ee9a105 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -84,23 +84,11 @@ FIND_LLVM_PROG([OPT], [opt], [opt], [$LlvmVersion]) OptCmd="$OPT" AC_SUBST([OptCmd]) -dnl ** Which ld to use? -dnl -------------------------------------------------------------- -FIND_LD([LdCmd]) -AC_SUBST([LdCmd]) - FP_GCC_VERSION FP_GCC_SUPPORTS_NO_PIE AC_PROG_CPP -FP_PROG_LD_IS_GNU -FP_PROG_LD_BUILD_ID -FP_PROG_LD_NO_COMPACT_UNWIND -FP_PROG_LD_FILELIST - -# dnl ** Check gcc version and flags we need to pass it ** -# FP_GCC_EXTRA_FLAGS FP_SET_CFLAGS_C99([CC],[CFLAGS],[CPPFLAGS]) @@ -127,6 +115,19 @@ AC_SUBST(CONF_CPP_OPTS_STAGE0) AC_SUBST(CONF_CPP_OPTS_STAGE1) AC_SUBST(CONF_CPP_OPTS_STAGE2) +dnl ** Which ld to use? +dnl -------------------------------------------------------------- +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" +AC_SUBST([LdCmd]) + +FP_PROG_LD_IS_GNU +FP_PROG_LD_BUILD_ID +FP_PROG_LD_NO_COMPACT_UNWIND +FP_PROG_LD_FILELIST + dnl ** Set up the variables for the platform in the settings file. dnl May need to use gcc to find platform details. dnl -------------------------------------------------------------- diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index f32a35b..e02f880 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -169,6 +169,10 @@ def checkDynAsm(actual_file, normaliser): actual = actual_str.split() if actual == ['initArray1', 'initArray2', 'ctors1', 'ctors2', 'success']: return 1 + elif actual == ['initArray1', 'initArray2', 'ctors2', 'ctors1', 'success']: + # gold seems to produce this ordering; this is slightly odd but if it's + # wrong it's not our fault. See #13883. + return 1 elif actual == ['ctors1', 'ctors2', 'initArray1', 'initArray2', 'success']: if_verbose(1, 'T5435_dyn_asm detected old-style dlopen, see #8458') return 1 From git at git.haskell.org Fri Jun 30 13:23:02 2017 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Jun 2017 13:23:02 +0000 (UTC) Subject: [commit: ghc] ghc-8.2: Bump haddock submodule (8c7ec7e) Message-ID: <20170630132302.BD1233A585@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.2 Link : http://ghc.haskell.org/trac/ghc/changeset/8c7ec7ea7233a771a4e761bbbbe5c250c6c5ab32/ghc >--------------------------------------------------------------- commit 8c7ec7ea7233a771a4e761bbbbe5c250c6c5ab32 Author: Ben Gamari Date: Fri Jun 30 09:22:21 2017 -0400 Bump haddock submodule Fixes a rather bad regression between 2.16 and 2.17 where it didn't show per argument documentation on class methods >--------------------------------------------------------------- 8c7ec7ea7233a771a4e761bbbbe5c250c6c5ab32 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index d5d8cd1..af3e6c7 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit d5d8cd1722b06f17155e830f2242a073b0a983eb +Subproject commit af3e6c7c027389df18b15ee9a9d72ffc97dc1852